singletons-0.10.0: A framework for generating singleton types

Copyright(C) 2013 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Maybe

Contents

Description

Defines functions and datatypes relating to the singleton for Maybe, including a singletons 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

Documentation

data family Sing a Source

The singleton kind-indexed data family.

Instances

TestCoercion * (Sing *) 
SDecide k (KProxy k) => TestEquality k (Sing k) 
data Sing Bool where 
data Sing Ordering where 
data Sing * where 
data Sing Nat where 
data Sing Symbol where 
data Sing () where 
data Sing [a0] where 
data Sing (Maybe a0) where 
data Sing (Either a0 b0) where 
data Sing ((,) a0 b0) where 
data Sing ((,,) a0 b0 c0) where 
data Sing ((,,,) a0 b0 c0 d0) where 
data Sing ((,,,,) a0 b0 c0 d0 e0) where 
data Sing ((,,,,,) a0 b0 c0 d0 e0 f0) where 
data Sing ((,,,,,,) a0 b0 c0 d0 e0 f0 g0) where 

Though Haddock doesn't show it, the Sing instance above declares constructors

SNothing :: Sing Nothing
SJust    :: Sing a -> Sing (Just a)

type SMaybe z = Sing z Source

SBool is a kind-restricted synonym for Sing: type SMaybe (a :: Maybe k) = Sing a

Singletons from Data.Maybe

type family Maybe_ a a a :: b Source

Equations

Maybe_ n z Nothing = n 
Maybe_ z f (Just x) = f x 

sMaybe_ :: forall t t t. Sing t -> (forall t. Sing t -> Sing (t t)) -> Sing t -> Sing (Maybe_ t t t) Source

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

type family IsJust a :: Bool Source

Equations

IsJust Nothing = False 
IsJust (Just z) = True 

sIsJust :: forall t. Sing t -> Sing (IsJust t) Source

type family IsNothing a :: Bool Source

sIsNothing :: forall t. Sing t -> Sing (IsNothing t) Source

type family FromJust a :: a Source

Equations

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

sFromJust :: forall t. Sing t -> Sing (FromJust t) Source

type family FromMaybe a a :: a Source

Equations

FromMaybe d Nothing = d 
FromMaybe z (Just v) = v 

sFromMaybe :: forall t t. Sing t -> Sing t -> Sing (FromMaybe t t) Source

type family MaybeToList a :: [a] Source

Equations

MaybeToList Nothing = `[]` 
MaybeToList (Just x) = `[x]` 

sMaybeToList :: forall t. Sing t -> Sing (MaybeToList t) Source

type family ListToMaybe a :: Maybe a Source

Equations

ListToMaybe [] = Nothing 
ListToMaybe ((:) a z) = Just a 

sListToMaybe :: forall t. Sing t -> Sing (ListToMaybe t) Source

type family CatMaybes a :: [a] Source

Equations

CatMaybes [] = `[]` 
CatMaybes ((:) (Just x) xs) = (:) x (CatMaybes xs) 
CatMaybes ((:) Nothing xs) = CatMaybes xs 

sCatMaybes :: forall t. Sing t -> Sing (CatMaybes t) Source

type family MapMaybe a a :: [b] Source

Equations

MapMaybe z [] = `[]` 
MapMaybe f ((:) x xs) = (:++) (MaybeToList (f x)) (MapMaybe f xs) 

sMapMaybe :: forall t t. (forall t. Sing t -> Sing (t t)) -> Sing t -> Sing (MapMaybe t t) Source