singletons-2.3: A framework for generating singleton types

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

Data.Promotion.Prelude.Either

Contents

Description

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

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

Synopsis

Promoted functions from Data.Either

either_ :: (a -> c) -> (b -> c) -> Either a b -> c Source #

type family Either_ (a :: TyFun a c -> Type) (a :: TyFun b c -> Type) (a :: Either a b) :: c where ... Source #

Equations

Either_ f _z_6989586621679433080 (Left x) = Apply f x 
Either_ _z_6989586621679433084 g (Right y) = Apply g y 

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

type family Lefts (a :: [Either a b]) :: [a] where ... Source #

Equations

Lefts '[] = '[] 
Lefts ((:) (Left x) xs) = Apply (Apply (:$) x) (Apply LeftsSym0 xs) 
Lefts ((:) (Right _z_6989586621679434267) xs) = Apply LeftsSym0 xs 

type family Rights (a :: [Either a b]) :: [b] where ... Source #

Equations

Rights '[] = '[] 
Rights ((:) (Left _z_6989586621679434255) xs) = Apply RightsSym0 xs 
Rights ((:) (Right x) xs) = Apply (Apply (:$) x) (Apply RightsSym0 xs) 

type family PartitionEithers (a :: [Either a b]) :: ([a], [b]) where ... Source #

Equations

PartitionEithers a_6989586621679434209 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Either_Sym0 (Let6989586621679434216LeftSym1 a_6989586621679434209)) (Let6989586621679434216RightSym1 a_6989586621679434209))) (Apply (Apply Tuple2Sym0 '[]) '[])) a_6989586621679434209 

type family IsLeft (a :: Either a b) :: Bool where ... Source #

Equations

IsLeft (Left _z_6989586621679434203) = TrueSym0 
IsLeft (Right _z_6989586621679434206) = FalseSym0 

type family IsRight (a :: Either a b) :: Bool where ... Source #

Equations

IsRight (Left _z_6989586621679434193) = FalseSym0 
IsRight (Right _z_6989586621679434196) = TrueSym0 

Defunctionalization symbols

data LeftSym0 (l :: TyFun a6989586621679072801 (Either a6989586621679072801 b6989586621679072802)) Source #

Instances

SuppressUnusedWarnings (TyFun a6989586621679072801 (Either a6989586621679072801 b6989586621679072802) -> *) (LeftSym0 a6989586621679072801 b6989586621679072802) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftSym0 a6989586621679072801 b6989586621679072802) t -> () Source #

type Apply a (Either a b6989586621679072802) (LeftSym0 a b6989586621679072802) l Source # 
type Apply a (Either a b6989586621679072802) (LeftSym0 a b6989586621679072802) l = Left a b6989586621679072802 l

type LeftSym1 (t :: a6989586621679072801) = Left t Source #

data RightSym0 (l :: TyFun b6989586621679072802 (Either a6989586621679072801 b6989586621679072802)) Source #

Instances

SuppressUnusedWarnings (TyFun b6989586621679072802 (Either a6989586621679072801 b6989586621679072802) -> *) (RightSym0 a6989586621679072801 b6989586621679072802) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightSym0 a6989586621679072801 b6989586621679072802) t -> () Source #

type Apply b (Either a6989586621679072801 b) (RightSym0 a6989586621679072801 b) l Source # 
type Apply b (Either a6989586621679072801 b) (RightSym0 a6989586621679072801 b) l = Right a6989586621679072801 b l

type RightSym1 (t :: b6989586621679072802) = Right t Source #

data Either_Sym0 (l :: TyFun (TyFun a6989586621679433056 c6989586621679433057 -> Type) (TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679433056 c6989586621679433057 -> Type) (TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) -> Type) -> *) (Either_Sym0 a6989586621679433056 b6989586621679433058 c6989586621679433057) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym0 a6989586621679433056 b6989586621679433058 c6989586621679433057) t -> () Source #

type Apply (TyFun a6989586621679433056 c6989586621679433057 -> Type) (TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) -> Type) (Either_Sym0 a6989586621679433056 b6989586621679433058 c6989586621679433057) l Source # 
type Apply (TyFun a6989586621679433056 c6989586621679433057 -> Type) (TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) -> Type) (Either_Sym0 a6989586621679433056 b6989586621679433058 c6989586621679433057) l = Either_Sym1 a6989586621679433056 b6989586621679433058 c6989586621679433057 l

data Either_Sym1 (l :: TyFun a6989586621679433056 c6989586621679433057 -> Type) (l :: TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679433056 c6989586621679433057 -> Type) -> TyFun (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) -> *) (Either_Sym1 a6989586621679433056 b6989586621679433058 c6989586621679433057) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym1 a6989586621679433056 b6989586621679433058 c6989586621679433057) t -> () Source #

type Apply (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) (Either_Sym1 a6989586621679433056 b6989586621679433058 c6989586621679433057 l1) l2 Source # 
type Apply (TyFun b6989586621679433058 c6989586621679433057 -> Type) (TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> Type) (Either_Sym1 a6989586621679433056 b6989586621679433058 c6989586621679433057 l1) l2 = Either_Sym2 a6989586621679433056 b6989586621679433058 c6989586621679433057 l1 l2

data Either_Sym2 (l :: TyFun a6989586621679433056 c6989586621679433057 -> Type) (l :: TyFun b6989586621679433058 c6989586621679433057 -> Type) (l :: TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679433056 c6989586621679433057 -> Type) -> (TyFun b6989586621679433058 c6989586621679433057 -> Type) -> TyFun (Either a6989586621679433056 b6989586621679433058) c6989586621679433057 -> *) (Either_Sym2 a6989586621679433056 b6989586621679433058 c6989586621679433057) Source # 

Methods

suppressUnusedWarnings :: Proxy (Either_Sym2 a6989586621679433056 b6989586621679433058 c6989586621679433057) t -> () Source #

type Apply (Either a b) c (Either_Sym2 a b c l1 l2) l3 Source # 
type Apply (Either a b) c (Either_Sym2 a b c l1 l2) l3 = Either_ a b c l1 l2 l3

type Either_Sym3 (t :: TyFun a6989586621679433056 c6989586621679433057 -> Type) (t :: TyFun b6989586621679433058 c6989586621679433057 -> Type) (t :: Either a6989586621679433056 b6989586621679433058) = Either_ t t t Source #

data LeftsSym0 (l :: TyFun [Either a6989586621679434168 b6989586621679434169] [a6989586621679434168]) Source #

Instances

SuppressUnusedWarnings (TyFun [Either a6989586621679434168 b6989586621679434169] [a6989586621679434168] -> *) (LeftsSym0 b6989586621679434169 a6989586621679434168) Source # 

Methods

suppressUnusedWarnings :: Proxy (LeftsSym0 b6989586621679434169 a6989586621679434168) t -> () Source #

type Apply [Either a b] [a] (LeftsSym0 b a) l Source # 
type Apply [Either a b] [a] (LeftsSym0 b a) l = Lefts b a l

type LeftsSym1 (t :: [Either a6989586621679434168 b6989586621679434169]) = Lefts t Source #

data RightsSym0 (l :: TyFun [Either a6989586621679434166 b6989586621679434167] [b6989586621679434167]) Source #

Instances

SuppressUnusedWarnings (TyFun [Either a6989586621679434166 b6989586621679434167] [b6989586621679434167] -> *) (RightsSym0 a6989586621679434166 b6989586621679434167) Source # 

Methods

suppressUnusedWarnings :: Proxy (RightsSym0 a6989586621679434166 b6989586621679434167) t -> () Source #

type Apply [Either a b] [b] (RightsSym0 a b) l Source # 
type Apply [Either a b] [b] (RightsSym0 a b) l = Rights a b l

type RightsSym1 (t :: [Either a6989586621679434166 b6989586621679434167]) = Rights t Source #

data IsLeftSym0 (l :: TyFun (Either a6989586621679434162 b6989586621679434163) Bool) Source #

Instances

SuppressUnusedWarnings (TyFun (Either a6989586621679434162 b6989586621679434163) Bool -> *) (IsLeftSym0 a6989586621679434162 b6989586621679434163) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsLeftSym0 a6989586621679434162 b6989586621679434163) t -> () Source #

type Apply (Either a b) Bool (IsLeftSym0 a b) l Source # 
type Apply (Either a b) Bool (IsLeftSym0 a b) l = IsLeft a b l

type IsLeftSym1 (t :: Either a6989586621679434162 b6989586621679434163) = IsLeft t Source #

data IsRightSym0 (l :: TyFun (Either a6989586621679434160 b6989586621679434161) Bool) Source #

Instances

SuppressUnusedWarnings (TyFun (Either a6989586621679434160 b6989586621679434161) Bool -> *) (IsRightSym0 a6989586621679434160 b6989586621679434161) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsRightSym0 a6989586621679434160 b6989586621679434161) t -> () Source #

type Apply (Either a b) Bool (IsRightSym0 a b) l Source # 
type Apply (Either a b) Bool (IsRightSym0 a b) l = IsRight a b l

type IsRightSym1 (t :: Either a6989586621679434160 b6989586621679434161) = IsRight t Source #