singleton-bool-0.1.6: Type level booleans
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Bool

Description

Additions to Data.Type.Bool.

Synopsis

Documentation

data SBool (b :: Bool) where Source #

Constructors

STrue :: SBool 'True 
SFalse :: SBool 'False 

Instances

Instances details
GShow SBool Source #
>>> showsPrec 0 STrue ""
"STrue"

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

gshowsPrec :: forall (a :: k). Int -> SBool a -> ShowS #

GRead SBool Source #
>>> readsPrec 0 "Some STrue" :: [(Some SBool, String)]
[(Some STrue,"")]
>>> readsPrec 0 "Some SFalse" :: [(Some SBool, String)]
[(Some SFalse,"")]
>>> readsPrec 0 "Some Else" :: [(Some SBool, String)]
[]

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

greadsPrec :: Int -> GReadS SBool #

GEq SBool Source #
>>> geq STrue STrue
Just Refl
>>> geq STrue SFalse
Nothing

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

geq :: forall (a :: k) (b :: k). SBool a -> SBool b -> Maybe (a :~: b) #

GCompare SBool Source #

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

gcompare :: forall (a :: k) (b :: k). SBool a -> SBool b -> GOrdering a b #

GNFData SBool Source #

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

grnf :: forall (a :: k). SBool a -> () #

Eq (SBool b) Source #

Since: 0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

(==) :: SBool b -> SBool b -> Bool #

(/=) :: SBool b -> SBool b -> Bool #

Ord (SBool b) Source #

Since: 0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

compare :: SBool b -> SBool b -> Ordering #

(<) :: SBool b -> SBool b -> Bool #

(<=) :: SBool b -> SBool b -> Bool #

(>) :: SBool b -> SBool b -> Bool #

(>=) :: SBool b -> SBool b -> Bool #

max :: SBool b -> SBool b -> SBool b #

min :: SBool b -> SBool b -> SBool b #

Show (SBool b) Source #

Since: 0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

showsPrec :: Int -> SBool b -> ShowS #

show :: SBool b -> String #

showList :: [SBool b] -> ShowS #

SBoolI b => Boring (SBool b) Source #

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

boring :: SBool b #

NFData (SBool b) Source #

Since: 0.1.6

Instance details

Defined in Data.Singletons.Bool

Methods

rnf :: SBool b -> () #

class SBoolI (b :: Bool) where Source #

Methods

sbool :: SBool b Source #

Instances

Instances details
SBoolI 'False Source # 
Instance details

Defined in Data.Singletons.Bool

Methods

sbool :: SBool 'False Source #

SBoolI 'True Source # 
Instance details

Defined in Data.Singletons.Bool

Methods

sbool :: SBool 'True Source #

fromSBool :: SBool b -> Bool Source #

Convert an SBool to the corresponding Bool.

Since: 0.1.4

withSomeSBool :: Bool -> (forall b. SBool b -> r) -> r Source #

Convert a normal Bool to an SBool, passing it into a continuation.

>>> withSomeSBool True fromSBool
True

Since: 0.1.4

reflectBool :: forall b proxy. SBoolI b => proxy b -> Bool Source #

Reflect to term-level.

>>> reflectBool (Proxy :: Proxy 'True)
True

reifyBool :: forall r. Bool -> (forall b. SBoolI b => Proxy b -> r) -> r Source #

Reify Bool to type-level.

>>> reifyBool True reflectBool
True

Data.Type.Dec

discreteBool is available with base >= 4.7 (GHC-7.8)

discreteBool :: forall a b. (SBoolI a, SBoolI b) => Dec (a :~: b) Source #

Decidable equality.

>>> decShow (discreteBool :: Dec ('True :~: 'True))
"Yes Refl"

Since: 0.1.5

Data.Type.Bool and .Equality

These are only defined with base >= 4.7

sboolAnd :: SBool a -> SBool b -> SBool (a && b) Source #

>>> sboolAnd STrue SFalse
SFalse

sboolOr :: SBool a -> SBool b -> SBool (a || b) Source #

eqToRefl :: (a == b) ~ 'True => a :~: b Source #

Since: 0.1.1.0

eqCast :: (a == b) ~ 'True => a -> b Source #

Since: 0.1.1.0

sboolEqRefl :: forall k (a :: k) (b :: k). SBoolI (a == b) => Maybe (a :~: b) Source #

Useful combination of sbool and eqToRefl

Since: 0.1.2.0

trivialRefl :: () :~: () Source #

Since: 0.1.1.0