defun-bool-0.1: Defunctionalization helpers: booleans
Safe HaskellTrustworthy
LanguageHaskell2010

SBool.DeFun

Description

Boolean functions.

Type families are defined in Data.Type.Bool module in base package. Term implementation use SBool from singleton-bool package.

Synopsis

Logical and

type LAnd (x :: Bool) (y :: Bool) = x && y #

Logical and. A synonym of &&

data LAndSym (x :: FunKind Bool (Bool ~> Bool)) #

Instances

Instances details
type App LAndSym (x :: Bool) 
Instance details

Defined in DeFun.Bool

type App LAndSym (x :: Bool) = LAndSym1 x

data LAndSym1 (x :: Bool) (y :: FunKind Bool Bool) #

Instances

Instances details
type App (LAndSym1 x :: FunKind Bool Bool -> Type) (y :: Bool) 
Instance details

Defined in DeFun.Bool

type App (LAndSym1 x :: FunKind Bool Bool -> Type) (y :: Bool) = LAnd x y

land :: SBool x -> SBool y -> SBool (LAnd x y) Source #

Logical or

type LOr (x :: Bool) (y :: Bool) = x || y #

Logical or. A synonym of ||

data LOrSym (x :: FunKind Bool (Bool ~> Bool)) #

Instances

Instances details
type App LOrSym (x :: Bool) 
Instance details

Defined in DeFun.Bool

type App LOrSym (x :: Bool) = LOrSym1 x

data LOrSym1 (x :: Bool) (y :: FunKind Bool Bool) #

Instances

Instances details
type App (LOrSym1 x :: FunKind Bool Bool -> Type) (y :: Bool) 
Instance details

Defined in DeFun.Bool

type App (LOrSym1 x :: FunKind Bool Bool -> Type) (y :: Bool) = LOr x y

lor :: SBool x -> SBool y -> SBool (LOr x y) Source #

Logical not

type family Not (a :: Bool) = (res :: Bool) | res -> a where ... #

Type-level "not". An injective type family since 4.10.0.0.

Since: base-4.7.0.0

Equations

Not 'False = 'True 
Not 'True = 'False 

data NotSym (x :: FunKind Bool Bool) #

Logical not.

Instances

Instances details
type App NotSym (x :: Bool) 
Instance details

Defined in DeFun.Bool

type App NotSym (x :: Bool) = Not x

not :: SBool x -> SBool (Not x) Source #