singletons-1.0: A framework for generating singleton types

Copyright(C) 2014 Jan Stolarek
LicenseBSD-style (see LICENSE)
MaintainerJan Stolarek (jan.stolarek@p.lodz.pl)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Promotion.Prelude.Bool

Contents

Description

Defines promoted functions and datatypes relating to Bool, including a promoted version of all the definitions in Data.Bool.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.Bool. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

Documentation

type family If cond tru fls :: k

Type-level If. If True a b ==> a; If False a b ==> b

Equations

If k True tru fls = tru 
If k False tru fls = fls 

Promoted functions from Data.Bool

type family Bool_ a a a :: a Source

Equations

Bool_ fls _tru False = fls 
Bool_ _fls tru True = tru 

bool_ :: forall a. a -> a -> Bool -> a Source

The preceding two definitions are derived from the function bool in Data.Bool. The extra underscore is to avoid name clashes with the type Bool.

type family Not a :: Bool Source

type family a :&& a :: Bool Source

Equations

False :&& z = FalseSym0 
True :&& x = x 

type family a :|| a :: Bool Source

Equations

False :|| x = x 
True :|| z = TrueSym0 

Defunctionalization symbols

type NotSym1 t = Not t Source

data (:&&$) l Source

Instances

data l :&&$$ l Source

Instances

type (:&&$$$) t t = (:&&) t t Source

data (:||$) l Source

Instances

data l :||$$ l Source

Instances

type (:||$$$) t t = (:||) t t Source

data Bool_Sym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k (TyFun Bool k -> *) -> *) -> *) (Bool_Sym0 k) 
type Apply (TyFun k (TyFun Bool k -> *) -> *) k (Bool_Sym0 k) l0 = Bool_Sym1 k l0 

data Bool_Sym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun k (TyFun Bool k -> *) -> *) (Bool_Sym1 k) 
type Apply (TyFun Bool k -> *) k (Bool_Sym1 k l1) l0 = Bool_Sym2 k l1 l0 

data Bool_Sym2 l l l Source

Instances

SuppressUnusedWarnings (k -> k -> TyFun Bool k -> *) (Bool_Sym2 k) 
type Apply k Bool (Bool_Sym2 k l1 l2) l0 = Bool_Sym3 k l1 l2 l0 

type Bool_Sym3 t t t = Bool_ t t t Source