singletons-2.3: 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 _z_6989586621679423233 Nothing = n 
Maybe_ _z_6989586621679423236 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 #

Equations

IsJust Nothing = FalseSym0 
IsJust (Just _z_6989586621679424445) = TrueSym0 

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

Equations

IsNothing Nothing = TrueSym0 
IsNothing (Just _z_6989586621679424438) = FalseSym0 

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_6989586621679424425 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_6989586621679424406) = 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 _z_6989586621679424358 '[] = '[] 
MapMaybe f ((:) x xs) = Case_6989586621679424390 f x xs (Let6989586621679424377Scrutinee_6989586621679424347Sym3 f x xs) 

Defunctionalization symbols

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

Instances

SuppressUnusedWarnings (TyFun a3530822107858468865 (Maybe a3530822107858468865) -> *) (JustSym0 a3530822107858468865) Source # 

Methods

suppressUnusedWarnings :: Proxy (JustSym0 a3530822107858468865) t -> () Source #

type Apply a (Maybe a) (JustSym0 a) l Source # 
type Apply a (Maybe a) (JustSym0 a) l = Just a l

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

data Maybe_Sym0 (l :: TyFun b6989586621679423211 (TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun b6989586621679423211 (TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) -> Type) -> *) (Maybe_Sym0 a6989586621679423212 b6989586621679423211) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym0 a6989586621679423212 b6989586621679423211) t -> () Source #

type Apply b6989586621679423211 (TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) -> Type) (Maybe_Sym0 a6989586621679423212 b6989586621679423211) l Source # 
type Apply b6989586621679423211 (TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) -> Type) (Maybe_Sym0 a6989586621679423212 b6989586621679423211) l = Maybe_Sym1 a6989586621679423212 b6989586621679423211 l

data Maybe_Sym1 (l :: b6989586621679423211) (l :: TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type)) Source #

Instances

SuppressUnusedWarnings (b6989586621679423211 -> TyFun (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) -> *) (Maybe_Sym1 a6989586621679423212 b6989586621679423211) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym1 a6989586621679423212 b6989586621679423211) t -> () Source #

type Apply (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) (Maybe_Sym1 a6989586621679423212 b6989586621679423211 l1) l2 Source # 
type Apply (TyFun a6989586621679423212 b6989586621679423211 -> Type) (TyFun (Maybe a6989586621679423212) b6989586621679423211 -> Type) (Maybe_Sym1 a6989586621679423212 b6989586621679423211 l1) l2 = Maybe_Sym2 a6989586621679423212 b6989586621679423211 l1 l2

data Maybe_Sym2 (l :: b6989586621679423211) (l :: TyFun a6989586621679423212 b6989586621679423211 -> Type) (l :: TyFun (Maybe a6989586621679423212) b6989586621679423211) Source #

Instances

SuppressUnusedWarnings (b6989586621679423211 -> (TyFun a6989586621679423212 b6989586621679423211 -> Type) -> TyFun (Maybe a6989586621679423212) b6989586621679423211 -> *) (Maybe_Sym2 a6989586621679423212 b6989586621679423211) Source # 

Methods

suppressUnusedWarnings :: Proxy (Maybe_Sym2 a6989586621679423212 b6989586621679423211) t -> () Source #

type Apply (Maybe a) b (Maybe_Sym2 a b l1 l2) l3 Source # 
type Apply (Maybe a) b (Maybe_Sym2 a b l1 l2) l3 = Maybe_ a b l1 l2 l3

type Maybe_Sym3 (t :: b6989586621679423211) (t :: TyFun a6989586621679423212 b6989586621679423211 -> Type) (t :: Maybe a6989586621679423212) = Maybe_ t t t Source #

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

Instances

SuppressUnusedWarnings (TyFun (Maybe a6989586621679424324) Bool -> *) (IsJustSym0 a6989586621679424324) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsJustSym0 a6989586621679424324) t -> () Source #

type Apply (Maybe a) Bool (IsJustSym0 a) l Source # 
type Apply (Maybe a) Bool (IsJustSym0 a) l = IsJust a l

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

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

Instances

SuppressUnusedWarnings (TyFun (Maybe a6989586621679424323) Bool -> *) (IsNothingSym0 a6989586621679424323) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsNothingSym0 a6989586621679424323) t -> () Source #

type Apply (Maybe a) Bool (IsNothingSym0 a) l Source # 
type Apply (Maybe a) Bool (IsNothingSym0 a) l = IsNothing a l

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

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

Instances

SuppressUnusedWarnings (TyFun (Maybe a6989586621679424322) a6989586621679424322 -> *) (FromJustSym0 a6989586621679424322) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromJustSym0 a6989586621679424322) t -> () Source #

type Apply (Maybe a) a (FromJustSym0 a) l Source # 
type Apply (Maybe a) a (FromJustSym0 a) l = FromJust a l

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679424321 (TyFun (Maybe a6989586621679424321) a6989586621679424321 -> Type) -> *) (FromMaybeSym0 a6989586621679424321) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym0 a6989586621679424321) t -> () Source #

type Apply a6989586621679424321 (TyFun (Maybe a6989586621679424321) a6989586621679424321 -> Type) (FromMaybeSym0 a6989586621679424321) l Source # 
type Apply a6989586621679424321 (TyFun (Maybe a6989586621679424321) a6989586621679424321 -> Type) (FromMaybeSym0 a6989586621679424321) l = FromMaybeSym1 a6989586621679424321 l

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

Instances

SuppressUnusedWarnings (a6989586621679424321 -> TyFun (Maybe a6989586621679424321) a6989586621679424321 -> *) (FromMaybeSym1 a6989586621679424321) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromMaybeSym1 a6989586621679424321) t -> () Source #

type Apply (Maybe a) a (FromMaybeSym1 a l1) l2 Source # 
type Apply (Maybe a) a (FromMaybeSym1 a l1) l2 = FromMaybe a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (Maybe a6989586621679424320) [a6989586621679424320] -> *) (MaybeToListSym0 a6989586621679424320) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaybeToListSym0 a6989586621679424320) t -> () Source #

type Apply (Maybe a) [a] (MaybeToListSym0 a) l Source # 
type Apply (Maybe a) [a] (MaybeToListSym0 a) l = MaybeToList a l

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

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679424319] (Maybe a6989586621679424319) -> *) (ListToMaybeSym0 a6989586621679424319) Source # 

Methods

suppressUnusedWarnings :: Proxy (ListToMaybeSym0 a6989586621679424319) t -> () Source #

type Apply [a] (Maybe a) (ListToMaybeSym0 a) l Source # 
type Apply [a] (Maybe a) (ListToMaybeSym0 a) l = ListToMaybe a l

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

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

Instances

SuppressUnusedWarnings (TyFun [Maybe a6989586621679424318] [a6989586621679424318] -> *) (CatMaybesSym0 a6989586621679424318) Source # 

Methods

suppressUnusedWarnings :: Proxy (CatMaybesSym0 a6989586621679424318) t -> () Source #

type Apply [Maybe a] [a] (CatMaybesSym0 a) l Source # 
type Apply [Maybe a] [a] (CatMaybesSym0 a) l = CatMaybes a l

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

data MapMaybeSym0 (l :: TyFun (TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) (TyFun [a6989586621679424316] [b6989586621679424317] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) (TyFun [a6989586621679424316] [b6989586621679424317] -> Type) -> *) (MapMaybeSym0 a6989586621679424316 b6989586621679424317) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym0 a6989586621679424316 b6989586621679424317) t -> () Source #

type Apply (TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) (TyFun [a6989586621679424316] [b6989586621679424317] -> Type) (MapMaybeSym0 a6989586621679424316 b6989586621679424317) l Source # 
type Apply (TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) (TyFun [a6989586621679424316] [b6989586621679424317] -> Type) (MapMaybeSym0 a6989586621679424316 b6989586621679424317) l = MapMaybeSym1 a6989586621679424316 b6989586621679424317 l

data MapMaybeSym1 (l :: TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) (l :: TyFun [a6989586621679424316] [b6989586621679424317]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679424316 (Maybe b6989586621679424317) -> Type) -> TyFun [a6989586621679424316] [b6989586621679424317] -> *) (MapMaybeSym1 a6989586621679424316 b6989586621679424317) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapMaybeSym1 a6989586621679424316 b6989586621679424317) t -> () Source #

type Apply [a] [b] (MapMaybeSym1 a b l1) l2 Source # 
type Apply [a] [b] (MapMaybeSym1 a b l1) l2 = MapMaybe a b l1 l2

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