first-class-families-0.8.0.1: First-class type families
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.Bool

Description

Booleans.

Note that the operations from this module conflict with Data.Type.Bool.

Synopsis

Documentation

data UnBool :: Exp a -> Exp a -> Bool -> Exp a Source #

N.B.: The order of the two branches is the opposite of "if": UnBool ifFalse ifTrue bool.

This mirrors the default order of constructors:

data Bool = False | True
----------- False < True

Instances

Instances details
type Eval (UnBool fal tru 'True :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru 'True :: a -> Type) = Eval tru
type Eval (UnBool fal tru 'False :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru 'False :: a -> Type) = Eval fal

data (||) :: Bool -> Bool -> Exp Bool infixr 2 Source #

Instances

Instances details
type Eval ('False || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval ('False || b :: Bool -> Type) = b
type Eval ('True || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval ('True || b :: Bool -> Type) = 'True
type Eval (a || 'False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || 'False :: Bool -> Type) = a
type Eval (a || 'True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || 'True :: Bool -> Type) = 'True

data (&&) :: Bool -> Bool -> Exp Bool infixr 3 Source #

Instances

Instances details
type Eval ('False && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval ('False && b :: Bool -> Type) = 'False
type Eval ('True && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval ('True && b :: Bool -> Type) = b
type Eval (a && 'True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && 'True :: Bool -> Type) = a
type Eval (a && 'False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && 'False :: Bool -> Type) = 'False

data Not :: Bool -> Exp Bool Source #

Instances

Instances details
type Eval (Not 'False) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not 'False) = 'True
type Eval (Not 'True) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not 'True) = 'False