first-class-families-0.7.0.0: First class type families

Safe HaskellSafe
LanguageHaskell2010

Fcf.Data.Bool

Contents

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
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
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
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
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

Multi-way if

data Guarded :: a -> [Guard (a -> Exp Bool) (Exp b)] -> Exp b Source #

Deprecated: Use Case instead

A conditional choosing the first branch whose guard a -> Exp Bool accepts a given value a.

Example

type UnitPrefix n = Eval (Guarded n
  '[ TyEq 0 ':= Pure ""
   , TyEq 1 ':= Pure "deci"
   , TyEq 2 ':= Pure "hecto"
   , TyEq 3 ':= Pure "kilo"
   , TyEq 6 ':= Pure "mega"
   , TyEq 9 ':= Pure "giga"
   , Otherwise ':= Error "Something else"
   ])
Instances
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))

data Guard a b Source #

A fancy-looking pair type to use with Guarded.

Constructors

a := b infixr 0 
Instances
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))

type Otherwise = ConstFn True Source #

A catch-all guard for Guarded.