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 |
Implements promoted functions from GHC.Base module.
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 Prelude
. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
- type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
- type family (a :: [a]) :++ (a :: [a]) :: [a] where ...
- type family Otherwise :: Bool where ...
- type family Id (a :: a) :: a where ...
- type family Const (a :: a) (a :: b) :: a where ...
- type family ((a :: TyFun b c -> Type) :. (a :: TyFun a b -> Type)) (a :: a) :: c where ...
- type family (f :: TyFun a b -> *) $ (x :: a) :: b
- type family (f :: TyFun a b -> *) $! (x :: a) :: b
- type family Flip (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: b) (a :: a) :: c where ...
- type family Until (a :: TyFun a Bool -> Type) (a :: TyFun a a -> Type) (a :: a) :: a where ...
- type family AsTypeOf (a :: a) (a :: a) :: a where ...
- type family Seq (a :: a) (a :: b) :: b where ...
- data FoldrSym0 l
- data FoldrSym1 l l
- data FoldrSym2 l l l
- type FoldrSym3 t t t = Foldr t t t
- data MapSym0 l
- data MapSym1 l l
- type MapSym2 t t = Map t t
- data (:++$) l
- data l :++$$ l
- type (:++$$$) t t = (:++) t t
- type OtherwiseSym0 = Otherwise
- data IdSym0 l
- type IdSym1 t = Id t
- data ConstSym0 l
- data ConstSym1 l l
- type ConstSym2 t t = Const t t
- data (:.$) l
- data l :.$$ l
- data (l :.$$$ l) l
- type (:.$$$$) t t t = (:.) t t t
- data ($$) :: TyFun (TyFun a b -> *) (TyFun a b -> *) -> *
- data ($$$) :: (TyFun a b -> *) -> TyFun a b -> *
- type ($$$$) a b = ($) a b
- data ($!$) :: TyFun (TyFun a b -> *) (TyFun a b -> *) -> *
- data ($!$$) :: (TyFun a b -> *) -> TyFun a b -> *
- type ($!$$$) a b = ($!) a b
- data FlipSym0 l
- data FlipSym1 l l
- data FlipSym2 l l l
- type FlipSym3 t t t = Flip t t t
- data UntilSym0 l
- data UntilSym1 l l
- data UntilSym2 l l l
- type UntilSym3 t t t = Until t t t
- data AsTypeOfSym0 l
- data AsTypeOfSym1 l l
- type AsTypeOfSym2 t t = AsTypeOf t t
- data SeqSym0 l
- data SeqSym1 l l
- type SeqSym2 t t = Seq t t
Promoted functions from GHC.Base
type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ... Source #
type family ((a :: TyFun b c -> Type) :. (a :: TyFun a b -> Type)) (a :: a) :: c where ... infixr 9 Source #
type family Flip (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: b) (a :: a) :: c where ... Source #
type family Until (a :: TyFun a Bool -> Type) (a :: TyFun a a -> Type) (a :: a) :: a where ... Source #
Defunctionalization symbols
SuppressUnusedWarnings (TyFun (TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) (TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> Type) -> *) (FoldrSym0 a1627796657 b1627796658) Source # | |
type Apply (TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) (TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> Type) (FoldrSym0 a1627796657 b1627796658) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627796657 (TyFun b1627796658 b1627796658 -> Type) -> Type) -> TyFun b1627796658 (TyFun [a1627796657] b1627796658 -> Type) -> *) (FoldrSym1 a1627796657 b1627796658) Source # | |
type Apply b1627796658 (TyFun [a1627796657] b1627796658 -> Type) (FoldrSym1 a1627796657 b1627796658 l1) l0 Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627796655 b1627796656 -> Type) (TyFun [a1627796655] [b1627796656] -> Type) -> *) (MapSym0 a1627796655 b1627796656) Source # | |
type Apply (TyFun a1627796655 b1627796656 -> Type) (TyFun [a1627796655] [b1627796656] -> Type) (MapSym0 a1627796655 b1627796656) l0 Source # | |
type OtherwiseSym0 = Otherwise Source #
SuppressUnusedWarnings (TyFun (TyFun b1627796648 c1627796649 -> Type) (TyFun (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) -> Type) -> *) ((:.$) b1627796648 a1627796650 c1627796649) Source # | |
type Apply (TyFun b1627796648 c1627796649 -> Type) (TyFun (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) -> Type) ((:.$) b1627796648 a1627796650 c1627796649) l0 Source # | |
SuppressUnusedWarnings ((TyFun b1627796648 c1627796649 -> Type) -> TyFun (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) -> *) ((:.$$) a1627796650 b1627796648 c1627796649) Source # | |
type Apply (TyFun a1627796650 b1627796648 -> Type) (TyFun a1627796650 c1627796649 -> Type) ((:.$$) a1627796650 b1627796648 c1627796649 l1) l0 Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) (TyFun b1627796646 (TyFun a1627796645 c1627796647 -> Type) -> Type) -> *) (FlipSym0 b1627796646 a1627796645 c1627796647) Source # | |
type Apply (TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) (TyFun b1627796646 (TyFun a1627796645 c1627796647 -> Type) -> Type) (FlipSym0 b1627796646 a1627796645 c1627796647) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) -> TyFun b1627796646 (TyFun a1627796645 c1627796647 -> Type) -> *) (FlipSym1 a1627796645 b1627796646 c1627796647) Source # | |
type Apply b1627796646 (TyFun a1627796645 c1627796647 -> Type) (FlipSym1 a1627796645 b1627796646 c1627796647 l1) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627796645 (TyFun b1627796646 c1627796647 -> Type) -> Type) -> b1627796646 -> TyFun a1627796645 c1627796647 -> *) (FlipSym2 a1627796645 b1627796646 c1627796647) Source # | |
type Apply a1627796645 c1627796647 (FlipSym2 a1627796645 b1627796646 c1627796647 l1 l2) l0 Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627845465 Bool -> Type) (TyFun (TyFun a1627845465 a1627845465 -> Type) (TyFun a1627845465 a1627845465 -> Type) -> Type) -> *) (UntilSym0 a1627845465) Source # | |
type Apply (TyFun a1627845465 Bool -> Type) (TyFun (TyFun a1627845465 a1627845465 -> Type) (TyFun a1627845465 a1627845465 -> Type) -> Type) (UntilSym0 a1627845465) l0 Source # | |
SuppressUnusedWarnings ((TyFun a1627845465 Bool -> Type) -> TyFun (TyFun a1627845465 a1627845465 -> Type) (TyFun a1627845465 a1627845465 -> Type) -> *) (UntilSym1 a1627845465) Source # | |
type Apply (TyFun a1627845465 a1627845465 -> Type) (TyFun a1627845465 a1627845465 -> Type) (UntilSym1 a1627845465 l1) l0 Source # | |
data AsTypeOfSym0 l Source #
SuppressUnusedWarnings (TyFun a1627796644 (TyFun a1627796644 a1627796644 -> Type) -> *) (AsTypeOfSym0 a1627796644) Source # | |
type Apply a1627796644 (TyFun a1627796644 a1627796644 -> Type) (AsTypeOfSym0 a1627796644) l0 Source # | |
data AsTypeOfSym1 l l Source #
SuppressUnusedWarnings (a1627796644 -> TyFun a1627796644 a1627796644 -> *) (AsTypeOfSym1 a1627796644) Source # | |
type Apply a1627796644 a1627796644 (AsTypeOfSym1 a1627796644 l1) l0 Source # | |
type AsTypeOfSym2 t t = AsTypeOf t t Source #