| Copyright | (C) 2014 Jan Stolarek | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | Jan Stolarek (jan.stolarek@p.lodz.pl) | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Promotion.Prelude.Maybe
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.
- maybe_ :: forall b a. b -> (a -> b) -> Maybe a -> b
- type family Maybe_ (a :: b) (a :: TyFun a b -> Type) (a :: Maybe a) :: b where ...
- type family IsJust (a :: Maybe a) :: Bool where ...
- type family IsNothing (a :: Maybe a) :: Bool where ...
- type family FromJust (a :: Maybe a) :: a where ...
- type family FromMaybe (a :: a) (a :: Maybe a) :: a where ...
- type family MaybeToList (a :: Maybe a) :: [a] where ...
- type family ListToMaybe (a :: [a]) :: Maybe a where ...
- type family CatMaybes (a :: [Maybe a]) :: [a] where ...
- type family MapMaybe (a :: TyFun a (Maybe b) -> Type) (a :: [a]) :: [b] where ...
- type NothingSym0 = Nothing
- data JustSym0 l
- type JustSym1 t = Just t
- data Maybe_Sym0 l
- data Maybe_Sym1 l l
- data Maybe_Sym2 l l l
- type Maybe_Sym3 t t t = Maybe_ t t t
- data IsJustSym0 l
- type IsJustSym1 t = IsJust t
- data IsNothingSym0 l
- type IsNothingSym1 t = IsNothing t
- data FromJustSym0 l
- type FromJustSym1 t = FromJust t
- data FromMaybeSym0 l
- data FromMaybeSym1 l l
- type FromMaybeSym2 t t = FromMaybe t t
- data MaybeToListSym0 l
- type MaybeToListSym1 t = MaybeToList t
- data ListToMaybeSym0 l
- type ListToMaybeSym1 t = ListToMaybe t
- data CatMaybesSym0 l
- type CatMaybesSym1 t = CatMaybes t
- data MapMaybeSym0 l
- data MapMaybeSym1 l l
- type MapMaybeSym2 t t = MapMaybe t t
Promoted functions from Data.Maybe
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 FromMaybe (a :: a) (a :: Maybe a) :: a where ... Source #
Equations
| FromMaybe d x = Case_1627849137 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 _z_1627849118) = Apply JustSym0 a | 
Defunctionalization symbols
type NothingSym0 = Nothing Source #
data Maybe_Sym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun b1627847771 (TyFun (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) -> Type) -> *) (Maybe_Sym0 a1627847772 b1627847771) Source # | |
| type Apply b1627847771 (TyFun (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) -> Type) (Maybe_Sym0 a1627847772 b1627847771) l0 Source # | |
data Maybe_Sym1 l l Source #
Instances
| SuppressUnusedWarnings (b1627847771 -> TyFun (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) -> *) (Maybe_Sym1 a1627847772 b1627847771) Source # | |
| type Apply (TyFun a1627847772 b1627847771 -> Type) (TyFun (Maybe a1627847772) b1627847771 -> Type) (Maybe_Sym1 a1627847772 b1627847771 l1) l0 Source # | |
data Maybe_Sym2 l l l Source #
Instances
| SuppressUnusedWarnings (b1627847771 -> (TyFun a1627847772 b1627847771 -> Type) -> TyFun (Maybe a1627847772) b1627847771 -> *) (Maybe_Sym2 a1627847772 b1627847771) Source # | |
| type Apply (Maybe a1627847772) b1627847771 (Maybe_Sym2 a1627847772 b1627847771 l1 l2) l0 Source # | |
type Maybe_Sym3 t t t = Maybe_ t t t Source #
data IsJustSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun (Maybe a1627849036) Bool -> *) (IsJustSym0 a1627849036) Source # | |
| type Apply (Maybe a1627849036) Bool (IsJustSym0 a1627849036) l0 Source # | |
type IsJustSym1 t = IsJust t Source #
data IsNothingSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun (Maybe a1627849035) Bool -> *) (IsNothingSym0 a1627849035) Source # | |
| type Apply (Maybe a1627849035) Bool (IsNothingSym0 a1627849035) l0 Source # | |
type IsNothingSym1 t = IsNothing t Source #
data FromJustSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun (Maybe a1627849034) a1627849034 -> *) (FromJustSym0 a1627849034) Source # | |
| type Apply (Maybe a1627849034) a1627849034 (FromJustSym0 a1627849034) l0 Source # | |
type FromJustSym1 t = FromJust t Source #
data FromMaybeSym0 l Source #
data FromMaybeSym1 l l Source #
Instances
| SuppressUnusedWarnings (a1627849033 -> TyFun (Maybe a1627849033) a1627849033 -> *) (FromMaybeSym1 a1627849033) Source # | |
| type Apply (Maybe a1627849033) a1627849033 (FromMaybeSym1 a1627849033 l1) l0 Source # | |
type FromMaybeSym2 t t = FromMaybe t t Source #
data MaybeToListSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun (Maybe a1627849032) [a1627849032] -> *) (MaybeToListSym0 a1627849032) Source # | |
| type Apply (Maybe a1627849032) [a1627849032] (MaybeToListSym0 a1627849032) l0 Source # | |
type MaybeToListSym1 t = MaybeToList t Source #
data ListToMaybeSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun [a1627849031] (Maybe a1627849031) -> *) (ListToMaybeSym0 a1627849031) Source # | |
| type Apply [a1627849031] (Maybe a1627849031) (ListToMaybeSym0 a1627849031) l0 Source # | |
type ListToMaybeSym1 t = ListToMaybe t Source #
data CatMaybesSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun [Maybe a1627849030] [a1627849030] -> *) (CatMaybesSym0 a1627849030) Source # | |
| type Apply [Maybe a1627849030] [a1627849030] (CatMaybesSym0 a1627849030) l0 Source # | |
type CatMaybesSym1 t = CatMaybes t Source #
data MapMaybeSym0 l Source #
Instances
| SuppressUnusedWarnings (TyFun (TyFun a1627849028 (Maybe b1627849029) -> Type) (TyFun [a1627849028] [b1627849029] -> Type) -> *) (MapMaybeSym0 a1627849028 b1627849029) Source # | |
| type Apply (TyFun a1627849028 (Maybe b1627849029) -> Type) (TyFun [a1627849028] [b1627849029] -> Type) (MapMaybeSym0 a1627849028 b1627849029) l0 Source # | |
data MapMaybeSym1 l l Source #
Instances
| SuppressUnusedWarnings ((TyFun a1627849028 (Maybe b1627849029) -> Type) -> TyFun [a1627849028] [b1627849029] -> *) (MapMaybeSym1 a1627849028 b1627849029) Source # | |
| type Apply [a1627849028] [b1627849029] (MapMaybeSym1 a1627849028 b1627849029 l1) l0 Source # | |
type MapMaybeSym2 t t = MapMaybe t t Source #