| Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Singletons.Prelude.Either
Description
Defines functions and datatypes relating to the singleton for Either,
including a singletons 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
- data family Sing (a :: k)
- type SEither = (Sing :: Either a b -> Type)
- either_ :: (a -> c) -> (b -> c) -> Either a b -> c
- type family Either_ (a :: TyFun a c -> Type) (a :: TyFun b c -> Type) (a :: Either a b) :: c where ...
- sEither_ :: forall (t :: TyFun a c -> Type) (t :: TyFun b c -> Type) (t :: Either a b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Either_Sym0 t) t) t :: c)
- type family Lefts (a :: [Either a b]) :: [a] where ...
- sLefts :: forall (t :: [Either a b]). Sing t -> Sing (Apply LeftsSym0 t :: [a])
- type family Rights (a :: [Either a b]) :: [b] where ...
- sRights :: forall (t :: [Either a b]). Sing t -> Sing (Apply RightsSym0 t :: [b])
- type family PartitionEithers (a :: [Either a b]) :: ([a], [b]) where ...
- sPartitionEithers :: forall (t :: [Either a b]). Sing t -> Sing (Apply PartitionEithersSym0 t :: ([a], [b]))
- type family IsLeft (a :: Either a b) :: Bool where ...
- sIsLeft :: forall (t :: Either a b). Sing t -> Sing (Apply IsLeftSym0 t :: Bool)
- type family IsRight (a :: Either a b) :: Bool where ...
- sIsRight :: forall (t :: Either a b). Sing t -> Sing (Apply IsRightSym0 t :: Bool)
- data LeftSym0 (l :: TyFun a6989586621679084181 (Either a6989586621679084181 b6989586621679084182))
- type LeftSym1 (t :: a6989586621679084181) = Left t
- data RightSym0 (l :: TyFun b6989586621679084182 (Either a6989586621679084181 b6989586621679084182))
- type RightSym1 (t :: b6989586621679084182) = Right t
- data Either_Sym0 (l :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type))
- data Either_Sym1 (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (l :: TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type))
- data Either_Sym2 (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (l :: TyFun b6989586621679992219 c6989586621679992218 -> Type) (l :: TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218)
- type Either_Sym3 (t :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (t :: TyFun b6989586621679992219 c6989586621679992218 -> Type) (t :: Either a6989586621679992217 b6989586621679992219) = Either_ t t t
- data LeftsSym0 (l :: TyFun [Either a6989586621679993353 b6989586621679993354] [a6989586621679993353])
- type LeftsSym1 (t :: [Either a6989586621679993353 b6989586621679993354]) = Lefts t
- data RightsSym0 (l :: TyFun [Either a6989586621679993351 b6989586621679993352] [b6989586621679993352])
- type RightsSym1 (t :: [Either a6989586621679993351 b6989586621679993352]) = Rights t
- data IsLeftSym0 (l :: TyFun (Either a6989586621679993347 b6989586621679993348) Bool)
- type IsLeftSym1 (t :: Either a6989586621679993347 b6989586621679993348) = IsLeft t
- data IsRightSym0 (l :: TyFun (Either a6989586621679993345 b6989586621679993346) Bool)
- type IsRightSym1 (t :: Either a6989586621679993345 b6989586621679993346) = IsRight t
The Either singleton
data family Sing (a :: k) Source #
The singleton kind-indexed data family.
Instances
Though Haddock doesn't show it, the Sing instance above declares
constructors
SLeft :: Sing a -> Sing (Left a) SRight :: Sing b -> Sing (Right b)
Singletons from Data.Either
type family Either_ (a :: TyFun a c -> Type) (a :: TyFun b c -> Type) (a :: Either a b) :: c where ... Source #
sEither_ :: forall (t :: TyFun a c -> Type) (t :: TyFun b c -> Type) (t :: Either a b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Either_Sym0 t) t) t :: c) Source #
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 PartitionEithers (a :: [Either a b]) :: ([a], [b]) where ... Source #
Equations
| PartitionEithers a_6989586621679993720 = Apply (Apply (Apply FoldrSym0 (Apply (Apply Either_Sym0 (Let6989586621679993727LeftSym1 a_6989586621679993720)) (Let6989586621679993727RightSym1 a_6989586621679993720))) (Apply (Apply Tuple2Sym0 '[]) '[])) a_6989586621679993720 |
sPartitionEithers :: forall (t :: [Either a b]). Sing t -> Sing (Apply PartitionEithersSym0 t :: ([a], [b])) Source #
Defunctionalization symbols
data LeftSym0 (l :: TyFun a6989586621679084181 (Either a6989586621679084181 b6989586621679084182)) Source #
Instances
| SuppressUnusedWarnings (LeftSym0 :: TyFun a6989586621679084181 (Either a6989586621679084181 b6989586621679084182) -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
| type Apply (LeftSym0 :: TyFun a (Either a b6989586621679084182) -> *) (l :: a) Source # | |
data RightSym0 (l :: TyFun b6989586621679084182 (Either a6989586621679084181 b6989586621679084182)) Source #
Instances
| SuppressUnusedWarnings (RightSym0 :: TyFun b6989586621679084182 (Either a6989586621679084181 b6989586621679084182) -> *) Source # | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () Source # | |
| type Apply (RightSym0 :: TyFun b (Either a6989586621679084181 b) -> *) (l :: b) Source # | |
data Either_Sym0 (l :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type)) Source #
Instances
| SuppressUnusedWarnings (Either_Sym0 :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Either_Sym0 :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type) -> *) (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (Either_Sym0 :: TyFun (TyFun a6989586621679992217 c6989586621679992218 -> Type) (TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> Type) -> *) (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) = (Either_Sym1 l :: TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> *) | |
data Either_Sym1 (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (l :: TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type)) Source #
Instances
| SuppressUnusedWarnings (Either_Sym1 :: (TyFun a6989586621679992217 c6989586621679992218 -> Type) -> TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Either_Sym1 l1 :: TyFun (TyFun b6989586621679992219 c6989586621679992218 -> Type) (TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> Type) -> *) (l2 :: TyFun b6989586621679992219 c6989586621679992218 -> Type) Source # | |
Defined in Data.Singletons.Prelude.Either | |
data Either_Sym2 (l :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (l :: TyFun b6989586621679992219 c6989586621679992218 -> Type) (l :: TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218) Source #
Instances
| SuppressUnusedWarnings (Either_Sym2 :: (TyFun a6989586621679992217 c6989586621679992218 -> Type) -> (TyFun b6989586621679992219 c6989586621679992218 -> Type) -> TyFun (Either a6989586621679992217 b6989586621679992219) c6989586621679992218 -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (Either_Sym2 l1 l2 :: TyFun (Either a b) c -> *) (l3 :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either | |
type Either_Sym3 (t :: TyFun a6989586621679992217 c6989586621679992218 -> Type) (t :: TyFun b6989586621679992219 c6989586621679992218 -> Type) (t :: Either a6989586621679992217 b6989586621679992219) = Either_ t t t Source #
data LeftsSym0 (l :: TyFun [Either a6989586621679993353 b6989586621679993354] [a6989586621679993353]) Source #
Instances
| SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a6989586621679993353 b6989586621679993354] [a6989586621679993353] -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> *) (l :: [Either a b]) Source # | |
data RightsSym0 (l :: TyFun [Either a6989586621679993351 b6989586621679993352] [b6989586621679993352]) Source #
Instances
| SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a6989586621679993351 b6989586621679993352] [b6989586621679993352] -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (RightsSym0 :: TyFun [Either a b] [b] -> *) (l :: [Either a b]) Source # | |
Defined in Data.Singletons.Prelude.Either | |
type RightsSym1 (t :: [Either a6989586621679993351 b6989586621679993352]) = Rights t Source #
data IsLeftSym0 (l :: TyFun (Either a6989586621679993347 b6989586621679993348) Bool) Source #
Instances
| SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621679993347 b6989586621679993348) Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either | |
type IsLeftSym1 (t :: Either a6989586621679993347 b6989586621679993348) = IsLeft t Source #
data IsRightSym0 (l :: TyFun (Either a6989586621679993345 b6989586621679993346) Bool) Source #
Instances
| SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621679993345 b6989586621679993346) Bool -> *) Source # | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () Source # | |
| type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> *) (l :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either | |
type IsRightSym1 (t :: Either a6989586621679993345 b6989586621679993346) = IsRight t Source #