Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Type level booleans
Synopsis
- type family If (c :: Bool) (t :: k) (e :: k) where ...
- type family NotB x where ...
- type family OrB x y where ...
- type family AndB x y where ...
- type family XorB x y where ...
- class KnownBool a where
- type family Not (t :: b) (f :: b) (x :: b) :: b where ...
- type family And (t :: b) (f :: b) (x :: b) (y :: b) :: b where ...
- type family Or (t :: b) (f :: b) (x :: b) (y :: b) :: b where ...
- type family Xor (t :: b) (f :: b) (x :: b) (y :: b) :: b where ...
- type family AndMany (t :: b) (f :: b) (xs :: [b]) :: b where ...
- type family OrMany (t :: b) (f :: b) (xs :: [b]) :: b where ...
- type family XorMany (t :: b) (f :: b) (xs :: [b]) :: b where ...
- type family AllFalse (t :: b) (f :: b) (xs :: [b]) :: b where ...
- type family AllTrue (t :: b) (f :: b) (xs :: [b]) :: b where ...
Documentation
type family NotB x where ... Source #
Boolean Not
>>>
boolValue @(NotB 'True)
False>>>
boolValue @(NotB 'False)
True
type family OrB x y where ... Source #
Boolean Or
>>>
boolValue @(OrB 'True 'False)
True>>>
boolValue @(OrB 'False 'False)
False
type family AndB x y where ... Source #
Boolean And
>>>
boolValue @(AndB 'True 'False)
False>>>
boolValue @(AndB 'True 'True)
True
type family XorB x y where ... Source #
Boolean Xor
>>>
boolValue @(XorB 'True 'False)
True>>>
boolValue @(XorB 'False 'False)
False>>>
boolValue @(XorB 'True 'True)
False
class KnownBool a where Source #
Type-level Bool known at compile time
Get a bool value from a Bool at type level
>>>
boolValue @'True
True>>>
boolValue @(AndB 'True 'False)
False
Generic
type family Not (t :: b) (f :: b) (x :: b) :: b where ... Source #
Generic boolean Not
>>>
natValue' @(Not 1 0 1 :: Nat)
0>>>
natValue' @(Not 1 0 0 :: Nat)
1
type family And (t :: b) (f :: b) (x :: b) (y :: b) :: b where ... Source #
Generic boolean And
>>>
natValue' @(And 1 0 1 0 :: Nat)
0>>>
natValue' @(And 1 0 1 1 :: Nat)
1
type family Or (t :: b) (f :: b) (x :: b) (y :: b) :: b where ... Source #
Generic boolean Or
>>>
natValue' @(Or 1 0 1 0 :: Nat)
1>>>
natValue' @(Or 1 0 0 0 :: Nat)
0
type family Xor (t :: b) (f :: b) (x :: b) (y :: b) :: b where ... Source #
Generic boolean Xor
>>>
natValue' @(Xor 1 0 1 0 :: Nat)
1>>>
natValue' @(Xor 1 0 0 0 :: Nat)
0>>>
natValue' @(Xor 1 0 1 1 :: Nat)
0
type family AndMany (t :: b) (f :: b) (xs :: [b]) :: b where ... Source #
Generic boolean And on a list
>>>
natValue' @(AndMany 1 0 '[1,0,1] :: Nat)
0>>>
natValue' @(AndMany 1 0 '[1,1,1] :: Nat)
1
type family OrMany (t :: b) (f :: b) (xs :: [b]) :: b where ... Source #
Generic boolean Or on a list
>>>
natValue' @(OrMany 1 0 '[1,0,1] :: Nat)
1>>>
natValue' @(OrMany 1 0 '[1,1,1] :: Nat)
1>>>
natValue' @(OrMany 1 0 '[0,0,0] :: Nat)
0
type family XorMany (t :: b) (f :: b) (xs :: [b]) :: b where ... Source #
Generic boolean Xor on a list (i.e. check if there is a single true element in the list)
>>>
natValue' @(XorMany 1 0 '[0,0,1] :: Nat)
1>>>
natValue' @(XorMany 1 0 '[1,0,1] :: Nat)
0>>>
natValue' @(XorMany 1 0 '[0,0,0] :: Nat)
0
type family AllFalse (t :: b) (f :: b) (xs :: [b]) :: b where ... Source #
Check if all the elements are false
>>>
natValue' @(AllFalse 1 0 '[0,0,1] :: Nat)
0>>>
natValue' @(AllFalse 1 0 '[0,0,0] :: Nat)
1