singletons-2.4.1: 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.Maybe

Contents

Description

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

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.Maybe. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

Promoted functions from Data.Maybe

maybe_ :: b -> (a -> b) -> Maybe a -> b Source #

type family Maybe_ (a :: b) (a :: TyFun a b -> Type) (a :: Maybe a) :: b where ... Source #

Equations

Maybe_ n _ Nothing = n 
Maybe_ _ f (Just x) = Apply f x 

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

type family IsJust (a :: Maybe a) :: Bool where ... Source #

type family IsNothing (a :: Maybe a) :: Bool where ... Source #

type family FromJust (a :: Maybe a) :: a where ... Source #

Equations

FromJust Nothing = Apply ErrorSym0 "Maybe.fromJust: Nothing" 
FromJust (Just x) = x 

type family FromMaybe (a :: a) (a :: Maybe a) :: a where ... Source #

Equations

FromMaybe d x = Case_6989586621679431214 d x x 

type family MaybeToList (a :: Maybe a) :: [a] where ... Source #

Equations

MaybeToList Nothing = '[] 
MaybeToList (Just x) = Apply (Apply (:@#@$) x) '[] 

type family ListToMaybe (a :: [a]) :: Maybe a where ... Source #

Equations

ListToMaybe '[] = NothingSym0 
ListToMaybe ((:) a _) = Apply JustSym0 a 

type family CatMaybes (a :: [Maybe a]) :: [a] where ... Source #

Equations

CatMaybes '[] = '[] 
CatMaybes ((:) (Just x) xs) = Apply (Apply (:@#@$) x) (Apply CatMaybesSym0 xs) 
CatMaybes ((:) Nothing xs) = Apply CatMaybesSym0 xs 

type family MapMaybe (a :: TyFun a (Maybe b) -> Type) (a :: [a]) :: [b] where ... Source #

Equations

MapMaybe _ '[] = '[] 
MapMaybe f ((:) x xs) = Case_6989586621679431182 f x xs (Let6989586621679431169Scrutinee_6989586621679431012Sym3 f x xs) 

Defunctionalization symbols

data JustSym0 (l :: TyFun a3530822107858468865 (Maybe a3530822107858468865)) Source #

Instances
SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> *) (l :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> *) (l :: a) = Just l

type JustSym1 (t :: a3530822107858468865) = Just t Source #

data Maybe_Sym0 (l :: TyFun b6989586621679429864 (TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679429864 (TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b6989586621679429864 (TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> Type) -> *) (l :: b6989586621679429864) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b6989586621679429864 (TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> Type) -> *) (l :: b6989586621679429864) = (Maybe_Sym1 l :: TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> *)

data Maybe_Sym1 (l :: b6989586621679429864) (l :: TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type)) Source #

Instances
SuppressUnusedWarnings (Maybe_Sym1 :: b6989586621679429864 -> TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 l1 :: TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> *) (l2 :: TyFun a6989586621679429865 b6989586621679429864 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 l1 :: TyFun (TyFun a6989586621679429865 b6989586621679429864 -> Type) (TyFun (Maybe a6989586621679429865) b6989586621679429864 -> Type) -> *) (l2 :: TyFun a6989586621679429865 b6989586621679429864 -> Type) = Maybe_Sym2 l1 l2

data Maybe_Sym2 (l :: b6989586621679429864) (l :: TyFun a6989586621679429865 b6989586621679429864 -> Type) (l :: TyFun (Maybe a6989586621679429865) b6989586621679429864) Source #

Instances
SuppressUnusedWarnings (Maybe_Sym2 :: b6989586621679429864 -> (TyFun a6989586621679429865 b6989586621679429864 -> Type) -> TyFun (Maybe a6989586621679429865) b6989586621679429864 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 l1 l2 :: TyFun (Maybe a) b -> *) (l3 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 l1 l2 :: TyFun (Maybe a) b -> *) (l3 :: Maybe a) = Maybe_ l1 l2 l3

type Maybe_Sym3 (t :: b6989586621679429864) (t :: TyFun a6989586621679429865 b6989586621679429864 -> Type) (t :: Maybe a6989586621679429865) = Maybe_ t t t Source #

data IsJustSym0 (l :: TyFun (Maybe a6989586621679430985) Bool) Source #

Instances
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679430985) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) = IsJust l

type IsJustSym1 (t :: Maybe a6989586621679430985) = IsJust t Source #

data IsNothingSym0 (l :: TyFun (Maybe a6989586621679430984) Bool) Source #

Instances
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679430984) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> *) (l :: Maybe a) = IsNothing l

type IsNothingSym1 (t :: Maybe a6989586621679430984) = IsNothing t Source #

data FromJustSym0 (l :: TyFun (Maybe a6989586621679430983) a6989586621679430983) Source #

Instances
SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679430983) a6989586621679430983 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> *) (l :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> *) (l :: Maybe a) = FromJust l

type FromJustSym1 (t :: Maybe a6989586621679430983) = FromJust t Source #

data FromMaybeSym0 (l :: TyFun a6989586621679430982 (TyFun (Maybe a6989586621679430982) a6989586621679430982 -> Type)) Source #

Instances
SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679430982 (TyFun (Maybe a6989586621679430982) a6989586621679430982 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a6989586621679430982 (TyFun (Maybe a6989586621679430982) a6989586621679430982 -> Type) -> *) (l :: a6989586621679430982) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a6989586621679430982 (TyFun (Maybe a6989586621679430982) a6989586621679430982 -> Type) -> *) (l :: a6989586621679430982) = FromMaybeSym1 l

data FromMaybeSym1 (l :: a6989586621679430982) (l :: TyFun (Maybe a6989586621679430982) a6989586621679430982) Source #

Instances
SuppressUnusedWarnings (FromMaybeSym1 :: a6989586621679430982 -> TyFun (Maybe a6989586621679430982) a6989586621679430982 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 l1 :: TyFun (Maybe a) a -> *) (l2 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 l1 :: TyFun (Maybe a) a -> *) (l2 :: Maybe a) = FromMaybe l1 l2

type FromMaybeSym2 (t :: a6989586621679430982) (t :: Maybe a6989586621679430982) = FromMaybe t t Source #

data MaybeToListSym0 (l :: TyFun (Maybe a6989586621679430981) [a6989586621679430981]) Source #

Instances
SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679430981) [a6989586621679430981] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> *) (l :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> *) (l :: Maybe a) = MaybeToList l

type MaybeToListSym1 (t :: Maybe a6989586621679430981) = MaybeToList t Source #

data ListToMaybeSym0 (l :: TyFun [a6989586621679430980] (Maybe a6989586621679430980)) Source #

Instances
SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679430980] (Maybe a6989586621679430980) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> *) (l :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> *) (l :: [a]) = ListToMaybe l

type ListToMaybeSym1 (t :: [a6989586621679430980]) = ListToMaybe t Source #

data CatMaybesSym0 (l :: TyFun [Maybe a6989586621679430979] [a6989586621679430979]) Source #

Instances
SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679430979] [a6989586621679430979] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> *) (l :: [Maybe a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> *) (l :: [Maybe a]) = CatMaybes l

type CatMaybesSym1 (t :: [Maybe a6989586621679430979]) = CatMaybes t Source #

data MapMaybeSym0 (l :: TyFun (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (TyFun [a6989586621679430977] [b6989586621679430978] -> Type)) Source #

Instances
SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (TyFun [a6989586621679430977] [b6989586621679430978] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (TyFun [a6989586621679430977] [b6989586621679430978] -> Type) -> *) (l :: TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (TyFun [a6989586621679430977] [b6989586621679430978] -> Type) -> *) (l :: TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) = MapMaybeSym1 l

data MapMaybeSym1 (l :: TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (l :: TyFun [a6989586621679430977] [b6989586621679430978]) Source #

Instances
SuppressUnusedWarnings (MapMaybeSym1 :: (TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) -> TyFun [a6989586621679430977] [b6989586621679430978] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) = MapMaybe l1 l2

type MapMaybeSym2 (t :: TyFun a6989586621679430977 (Maybe b6989586621679430978) -> Type) (t :: [a6989586621679430977]) = MapMaybe t t Source #