module Data.Bool.HT.Private where
import Data.List as List (find, )
import Data.Maybe as Maybe (fromMaybe, )
{-# INLINE if' #-}
if' :: Bool -> a -> a -> a
if' :: forall a. Bool -> a -> a -> a
if' Bool
True a
x a
_ = a
x
if' Bool
False a
_ a
y = a
y
{-# INLINE ifThenElse #-}
ifThenElse :: Bool -> a -> a -> a
ifThenElse :: forall a. Bool -> a -> a -> a
ifThenElse = forall a. Bool -> a -> a -> a
if'
{-# INLINE select #-}
select, select0, select1 :: a -> [(Bool, a)] -> a
select :: forall a. a -> [(Bool, a)] -> a
select a
def = forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
def forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find forall a b. (a, b) -> a
fst
select0 :: forall a. a -> [(Bool, a)] -> a
select0 a
def = forall a. a -> Maybe a -> a
fromMaybe a
def forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Bool
True
select1 :: forall a. a -> [(Bool, a)] -> a
select1 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Bool -> a -> a -> a
if')
zipIf :: [Bool] -> [a] -> [a] -> [a]
zipIf :: forall a. [Bool] -> [a] -> [a] -> [a]
zipIf = forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 forall a. Bool -> a -> a -> a
if'
infixr 1 ?:
{-# INLINE (?:) #-}
(?:) :: Bool -> (a,a) -> a
?: :: forall a. Bool -> (a, a) -> a
(?:) = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Bool -> a -> a -> a
if'
infixr 1 `implies`
{-# INLINE implies #-}
implies :: Bool -> Bool -> Bool
implies :: Bool -> Bool -> Bool
implies Bool
prerequisite Bool
conclusion =
Bool -> Bool
not Bool
prerequisite Bool -> Bool -> Bool
|| Bool
conclusion