singletons-2.4: 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.Base

Contents

Description

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.

Synopsis
  • 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 (a :: TyFun a b -> Type) $ (a :: a) :: b where ...
  • type family (a :: TyFun a b -> Type) $! (a :: a) :: b where ...
  • 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 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type))
  • data FoldrSym1 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type))
  • data FoldrSym2 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: b6989586621679419908) (l :: TyFun [a6989586621679419907] b6989586621679419908)
  • type FoldrSym3 (t :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (t :: b6989586621679419908) (t :: [a6989586621679419907]) = Foldr t t t
  • data MapSym0 (l :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type))
  • data MapSym1 (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (l :: TyFun [a6989586621679419905] [b6989586621679419906])
  • type MapSym2 (t :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (t :: [a6989586621679419905]) = Map t t
  • data (++@#@$) (l :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type))
  • data (l :: [a6989586621679419904]) ++@#@$$ (l :: TyFun [a6989586621679419904] [a6989586621679419904])
  • type (++@#@$$$) (t :: [a6989586621679419904]) (t :: [a6989586621679419904]) = (++) t t
  • type OtherwiseSym0 = Otherwise
  • data IdSym0 (l :: TyFun a6989586621679419903 a6989586621679419903)
  • type IdSym1 (t :: a6989586621679419903) = Id t
  • data ConstSym0 (l :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type))
  • data ConstSym1 (l :: a6989586621679419901) (l :: TyFun b6989586621679419902 a6989586621679419901)
  • type ConstSym2 (t :: a6989586621679419901) (t :: b6989586621679419902) = Const t t
  • data (.@#@$) (l :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type))
  • data (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$ (l :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type))
  • data ((l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$$ (l :: TyFun a6989586621679419900 b6989586621679419898 -> Type)) (l :: TyFun a6989586621679419900 c6989586621679419899)
  • type (.@#@$$$$) (t :: TyFun b6989586621679419898 c6989586621679419899 -> Type) (t :: TyFun a6989586621679419900 b6989586621679419898 -> Type) (t :: a6989586621679419900) = (:.) t t t
  • data ($@#@$) (l :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type))
  • data (l :: TyFun a6989586621679419892 b6989586621679419893 -> Type) $@#@$$ (l :: TyFun a6989586621679419892 b6989586621679419893)
  • type ($@#@$$$) (t :: TyFun a6989586621679419892 b6989586621679419893 -> Type) (t :: a6989586621679419892) = ($) t t
  • data ($!@#@$) (l :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type))
  • data (l :: TyFun a6989586621679419890 b6989586621679419891 -> Type) $!@#@$$ (l :: TyFun a6989586621679419890 b6989586621679419891)
  • type ($!@#@$$$) (t :: TyFun a6989586621679419890 b6989586621679419891 -> Type) (t :: a6989586621679419890) = ($!) t t
  • data FlipSym0 (l :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type))
  • data FlipSym1 (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (l :: TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type))
  • data FlipSym2 (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (l :: b6989586621679419896) (l :: TyFun a6989586621679419895 c6989586621679419897)
  • type FlipSym3 (t :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (t :: b6989586621679419896) (t :: a6989586621679419895) = Flip t t t
  • data UntilSym0 (l :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type))
  • data UntilSym1 (l :: TyFun a6989586621679958924 Bool -> Type) (l :: TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type))
  • data UntilSym2 (l :: TyFun a6989586621679958924 Bool -> Type) (l :: TyFun a6989586621679958924 a6989586621679958924 -> Type) (l :: TyFun a6989586621679958924 a6989586621679958924)
  • type UntilSym3 (t :: TyFun a6989586621679958924 Bool -> Type) (t :: TyFun a6989586621679958924 a6989586621679958924 -> Type) (t :: a6989586621679958924) = Until t t t
  • data AsTypeOfSym0 (l :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type))
  • data AsTypeOfSym1 (l :: a6989586621679419894) (l :: TyFun a6989586621679419894 a6989586621679419894)
  • type AsTypeOfSym2 (t :: a6989586621679419894) (t :: a6989586621679419894) = AsTypeOf t t
  • data SeqSym0 (l :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type))
  • data SeqSym1 (l :: a6989586621679419888) (l :: TyFun b6989586621679419889 b6989586621679419889)
  • type SeqSym2 (t :: a6989586621679419888) (t :: b6989586621679419889) = 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 #

Equations

Foldr k z a_6989586621679420172 = Apply (Let6989586621679420177GoSym3 k z a_6989586621679420172) a_6989586621679420172 

type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ... Source #

Equations

Map _ '[] = '[] 
Map f ((:) x xs) = Apply (Apply (:@#@$) (Apply f x)) (Apply (Apply MapSym0 f) xs) 

type family (a :: [a]) ++ (a :: [a]) :: [a] where ... Source #

Equations

'[] ++ ys = ys 
((:) x xs) ++ ys = Apply (Apply (:@#@$) x) (Apply (Apply (++@#@$) xs) ys) 

type family Otherwise :: Bool where ... Source #

Equations

Otherwise = TrueSym0 

type family Id (a :: a) :: a where ... Source #

Equations

Id x = x 

type family Const (a :: a) (a :: b) :: a where ... Source #

Equations

Const x _ = x 

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

Equations

(f :. g) a_6989586621679420075 = Apply (Apply (Apply (Apply Lambda_6989586621679420080Sym0 f) g) a_6989586621679420075) a_6989586621679420075 

type family (a :: TyFun a b -> Type) $ (a :: a) :: b where ... Source #

Equations

f $ x = Apply f x 

type family (a :: TyFun a b -> Type) $! (a :: a) :: b where ... Source #

Equations

f $! x = Apply f (Let6989586621679420023VxSym2 f x) 

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

Equations

Flip f x y = Apply (Apply f y) x 

type family Until (a :: TyFun a Bool -> Type) (a :: TyFun a a -> Type) (a :: a) :: a where ... Source #

Equations

Until p f a_6989586621679958947 = Apply (Let6989586621679958952GoSym3 p f a_6989586621679958947) a_6989586621679958947 

type family AsTypeOf (a :: a) (a :: a) :: a where ... Source #

Equations

AsTypeOf a_6989586621679420112 a_6989586621679420114 = Apply (Apply ConstSym0 a_6989586621679420112) a_6989586621679420114 

type family Seq (a :: a) (a :: b) :: b where ... infixr 0 Source #

Equations

Seq _ x = x 

Defunctionalization symbols

data FoldrSym0 (l :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) Source # 
Instance details
type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) Source # 
Instance details
type Apply (FoldrSym0 :: TyFun (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) = FoldrSym1 l

data FoldrSym1 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type)) Source #

Instances
SuppressUnusedWarnings (FoldrSym1 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) Source # 
Instance details
type Apply (FoldrSym1 l1 :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) (l2 :: b6989586621679419908) Source # 
Instance details
type Apply (FoldrSym1 l1 :: TyFun b6989586621679419908 (TyFun [a6989586621679419907] b6989586621679419908 -> Type) -> *) (l2 :: b6989586621679419908) = FoldrSym2 l1 l2

data FoldrSym2 (l :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (l :: b6989586621679419908) (l :: TyFun [a6989586621679419907] b6989586621679419908) Source #

Instances
SuppressUnusedWarnings (FoldrSym2 :: (TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) -> b6989586621679419908 -> TyFun [a6989586621679419907] b6989586621679419908 -> *) Source # 
Instance details
type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) Source # 
Instance details
type Apply (FoldrSym2 l1 l2 :: TyFun [a] b -> *) (l3 :: [a]) = Foldr l1 l2 l3

type FoldrSym3 (t :: TyFun a6989586621679419907 (TyFun b6989586621679419908 b6989586621679419908 -> Type) -> Type) (t :: b6989586621679419908) (t :: [a6989586621679419907]) = Foldr t t t Source #

data MapSym0 (l :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type)) Source #

Instances
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) Source # 
Instance details
type Apply (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) Source # 
Instance details
type Apply (MapSym0 :: TyFun (TyFun a6989586621679419905 b6989586621679419906 -> Type) (TyFun [a6989586621679419905] [b6989586621679419906] -> Type) -> *) (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) = MapSym1 l

data MapSym1 (l :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (l :: TyFun [a6989586621679419905] [b6989586621679419906]) Source #

Instances
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679419905 b6989586621679419906 -> Type) -> TyFun [a6989586621679419905] [b6989586621679419906] -> *) Source # 
Instance details
type Apply (MapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) Source # 
Instance details
type Apply (MapSym1 l1 :: TyFun [a] [b] -> *) (l2 :: [a]) = Map l1 l2

type MapSym2 (t :: TyFun a6989586621679419905 b6989586621679419906 -> Type) (t :: [a6989586621679419905]) = Map t t Source #

data (++@#@$) (l :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type)) Source #

Instances
SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) Source # 
Instance details
type Apply ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) (l :: [a6989586621679419904]) Source # 
Instance details
type Apply ((++@#@$) :: TyFun [a6989586621679419904] (TyFun [a6989586621679419904] [a6989586621679419904] -> Type) -> *) (l :: [a6989586621679419904]) = (++@#@$$) l

data (l :: [a6989586621679419904]) ++@#@$$ (l :: TyFun [a6989586621679419904] [a6989586621679419904]) Source #

Instances
SuppressUnusedWarnings ((++@#@$$) :: [a6989586621679419904] -> TyFun [a6989586621679419904] [a6989586621679419904] -> *) Source # 
Instance details
type Apply ((++@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) Source # 
Instance details
type Apply ((++@#@$$) l1 :: TyFun [a] [a] -> *) (l2 :: [a]) = l1 ++ l2

type (++@#@$$$) (t :: [a6989586621679419904]) (t :: [a6989586621679419904]) = (++) t t Source #

data IdSym0 (l :: TyFun a6989586621679419903 a6989586621679419903) Source #

Instances
SuppressUnusedWarnings (IdSym0 :: TyFun a6989586621679419903 a6989586621679419903 -> *) Source # 
Instance details
type Apply (IdSym0 :: TyFun a a -> *) (l :: a) Source # 
Instance details
type Apply (IdSym0 :: TyFun a a -> *) (l :: a) = Id l

type IdSym1 (t :: a6989586621679419903) = Id t Source #

data ConstSym0 (l :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type)) Source #

Instances
SuppressUnusedWarnings (ConstSym0 :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type) -> *) Source # 
Instance details
type Apply (ConstSym0 :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type) -> *) (l :: a6989586621679419901) Source # 
Instance details
type Apply (ConstSym0 :: TyFun a6989586621679419901 (TyFun b6989586621679419902 a6989586621679419901 -> Type) -> *) (l :: a6989586621679419901) = (ConstSym1 l :: TyFun b6989586621679419902 a6989586621679419901 -> *)

data ConstSym1 (l :: a6989586621679419901) (l :: TyFun b6989586621679419902 a6989586621679419901) Source #

Instances
SuppressUnusedWarnings (ConstSym1 :: a6989586621679419901 -> TyFun b6989586621679419902 a6989586621679419901 -> *) Source # 
Instance details
type Apply (ConstSym1 l1 :: TyFun b a -> *) (l2 :: b) Source # 
Instance details
type Apply (ConstSym1 l1 :: TyFun b a -> *) (l2 :: b) = Const l1 l2

type ConstSym2 (t :: a6989586621679419901) (t :: b6989586621679419902) = Const t t Source #

data (.@#@$) (l :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) Source # 
Instance details
type Apply ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) Source # 
Instance details
type Apply ((.@#@$) :: TyFun (TyFun b6989586621679419898 c6989586621679419899 -> Type) (TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> Type) -> *) (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) = ((.@#@$$) l :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *)

data (l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$ (l :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type)) Source #

Instances
SuppressUnusedWarnings ((.@#@$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) Source # 
Instance details
type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) (l2 :: TyFun a6989586621679419900 b6989586621679419898 -> Type) Source # 
Instance details
type Apply ((.@#@$$) l1 :: TyFun (TyFun a6989586621679419900 b6989586621679419898 -> Type) (TyFun a6989586621679419900 c6989586621679419899 -> Type) -> *) (l2 :: TyFun a6989586621679419900 b6989586621679419898 -> Type) = l1 .@#@$$$ l2

data ((l :: TyFun b6989586621679419898 c6989586621679419899 -> Type) .@#@$$$ (l :: TyFun a6989586621679419900 b6989586621679419898 -> Type)) (l :: TyFun a6989586621679419900 c6989586621679419899) Source #

Instances
SuppressUnusedWarnings ((.@#@$$$) :: (TyFun b6989586621679419898 c6989586621679419899 -> Type) -> (TyFun a6989586621679419900 b6989586621679419898 -> Type) -> TyFun a6989586621679419900 c6989586621679419899 -> *) Source # 
Instance details
type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) Source # 
Instance details
type Apply (l1 .@#@$$$ l2 :: TyFun a c -> *) (l3 :: a) = (l1 :. l2) l3

type (.@#@$$$$) (t :: TyFun b6989586621679419898 c6989586621679419899 -> Type) (t :: TyFun a6989586621679419900 b6989586621679419898 -> Type) (t :: a6989586621679419900) = (:.) t t t Source #

data ($@#@$) (l :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type)) Source #

Instances
SuppressUnusedWarnings (($@#@$) :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> *) Source # 
Instance details
type Apply (($@#@$) :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> *) (l :: TyFun a6989586621679419892 b6989586621679419893 -> Type) Source # 
Instance details
type Apply (($@#@$) :: TyFun (TyFun a6989586621679419892 b6989586621679419893 -> Type) (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> *) (l :: TyFun a6989586621679419892 b6989586621679419893 -> Type) = ($@#@$$) l

data (l :: TyFun a6989586621679419892 b6989586621679419893 -> Type) $@#@$$ (l :: TyFun a6989586621679419892 b6989586621679419893) Source #

Instances
SuppressUnusedWarnings (($@#@$$) :: (TyFun a6989586621679419892 b6989586621679419893 -> Type) -> TyFun a6989586621679419892 b6989586621679419893 -> *) Source # 
Instance details
type Apply (($@#@$$) l1 :: TyFun a b -> *) (l2 :: a) Source # 
Instance details
type Apply (($@#@$$) l1 :: TyFun a b -> *) (l2 :: a) = l1 $ l2

type ($@#@$$$) (t :: TyFun a6989586621679419892 b6989586621679419893 -> Type) (t :: a6989586621679419892) = ($) t t Source #

data ($!@#@$) (l :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type)) Source #

Instances
SuppressUnusedWarnings (($!@#@$) :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> *) Source # 
Instance details
type Apply (($!@#@$) :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> *) (l :: TyFun a6989586621679419890 b6989586621679419891 -> Type) Source # 
Instance details
type Apply (($!@#@$) :: TyFun (TyFun a6989586621679419890 b6989586621679419891 -> Type) (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> *) (l :: TyFun a6989586621679419890 b6989586621679419891 -> Type) = ($!@#@$$) l

data (l :: TyFun a6989586621679419890 b6989586621679419891 -> Type) $!@#@$$ (l :: TyFun a6989586621679419890 b6989586621679419891) Source #

Instances
SuppressUnusedWarnings (($!@#@$$) :: (TyFun a6989586621679419890 b6989586621679419891 -> Type) -> TyFun a6989586621679419890 b6989586621679419891 -> *) Source # 
Instance details
type Apply (($!@#@$$) l1 :: TyFun a b -> *) (l2 :: a) Source # 
Instance details
type Apply (($!@#@$$) l1 :: TyFun a b -> *) (l2 :: a) = l1 $! l2

type ($!@#@$$$) (t :: TyFun a6989586621679419890 b6989586621679419891 -> Type) (t :: a6989586621679419890) = ($!) t t Source #

data FlipSym0 (l :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (FlipSym0 :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type) -> *) Source # 
Instance details
type Apply (FlipSym0 :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) Source # 
Instance details
type Apply (FlipSym0 :: TyFun (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> Type) -> *) (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) = FlipSym1 l

data FlipSym1 (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (l :: TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type)) Source #

Instances
SuppressUnusedWarnings (FlipSym1 :: (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) -> TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> *) Source # 
Instance details
type Apply (FlipSym1 l1 :: TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> *) (l2 :: b6989586621679419896) Source # 
Instance details
type Apply (FlipSym1 l1 :: TyFun b6989586621679419896 (TyFun a6989586621679419895 c6989586621679419897 -> Type) -> *) (l2 :: b6989586621679419896) = FlipSym2 l1 l2

data FlipSym2 (l :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (l :: b6989586621679419896) (l :: TyFun a6989586621679419895 c6989586621679419897) Source #

Instances
SuppressUnusedWarnings (FlipSym2 :: (TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) -> b6989586621679419896 -> TyFun a6989586621679419895 c6989586621679419897 -> *) Source # 
Instance details
type Apply (FlipSym2 l1 l2 :: TyFun a c -> *) (l3 :: a) Source # 
Instance details
type Apply (FlipSym2 l1 l2 :: TyFun a c -> *) (l3 :: a) = Flip l1 l2 l3

type FlipSym3 (t :: TyFun a6989586621679419895 (TyFun b6989586621679419896 c6989586621679419897 -> Type) -> Type) (t :: b6989586621679419896) (t :: a6989586621679419895) = Flip t t t Source #

data UntilSym0 (l :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (UntilSym0 :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type) -> *) Source # 
Instance details
type Apply (UntilSym0 :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type) -> *) (l :: TyFun a6989586621679958924 Bool -> Type) Source # 
Instance details
type Apply (UntilSym0 :: TyFun (TyFun a6989586621679958924 Bool -> Type) (TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> Type) -> *) (l :: TyFun a6989586621679958924 Bool -> Type) = UntilSym1 l

data UntilSym1 (l :: TyFun a6989586621679958924 Bool -> Type) (l :: TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type)) Source #

Instances
SuppressUnusedWarnings (UntilSym1 :: (TyFun a6989586621679958924 Bool -> Type) -> TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> *) Source # 
Instance details
type Apply (UntilSym1 l1 :: TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> *) (l2 :: TyFun a6989586621679958924 a6989586621679958924 -> Type) Source # 
Instance details
type Apply (UntilSym1 l1 :: TyFun (TyFun a6989586621679958924 a6989586621679958924 -> Type) (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> *) (l2 :: TyFun a6989586621679958924 a6989586621679958924 -> Type) = UntilSym2 l1 l2

data UntilSym2 (l :: TyFun a6989586621679958924 Bool -> Type) (l :: TyFun a6989586621679958924 a6989586621679958924 -> Type) (l :: TyFun a6989586621679958924 a6989586621679958924) Source #

Instances
SuppressUnusedWarnings (UntilSym2 :: (TyFun a6989586621679958924 Bool -> Type) -> (TyFun a6989586621679958924 a6989586621679958924 -> Type) -> TyFun a6989586621679958924 a6989586621679958924 -> *) Source # 
Instance details
type Apply (UntilSym2 l1 l2 :: TyFun a a -> *) (l3 :: a) Source # 
Instance details
type Apply (UntilSym2 l1 l2 :: TyFun a a -> *) (l3 :: a) = Until l1 l2 l3

type UntilSym3 (t :: TyFun a6989586621679958924 Bool -> Type) (t :: TyFun a6989586621679958924 a6989586621679958924 -> Type) (t :: a6989586621679958924) = Until t t t Source #

data AsTypeOfSym0 (l :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type)) Source #

Instances
SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type) -> *) Source # 
Instance details
type Apply (AsTypeOfSym0 :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type) -> *) (l :: a6989586621679419894) Source # 
Instance details
type Apply (AsTypeOfSym0 :: TyFun a6989586621679419894 (TyFun a6989586621679419894 a6989586621679419894 -> Type) -> *) (l :: a6989586621679419894) = AsTypeOfSym1 l

data AsTypeOfSym1 (l :: a6989586621679419894) (l :: TyFun a6989586621679419894 a6989586621679419894) Source #

Instances
SuppressUnusedWarnings (AsTypeOfSym1 :: a6989586621679419894 -> TyFun a6989586621679419894 a6989586621679419894 -> *) Source # 
Instance details
type Apply (AsTypeOfSym1 l1 :: TyFun a a -> *) (l2 :: a) Source # 
Instance details
type Apply (AsTypeOfSym1 l1 :: TyFun a a -> *) (l2 :: a) = AsTypeOf l1 l2

type AsTypeOfSym2 (t :: a6989586621679419894) (t :: a6989586621679419894) = AsTypeOf t t Source #

data SeqSym0 (l :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type)) Source #

Instances
SuppressUnusedWarnings (SeqSym0 :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type) -> *) Source # 
Instance details
type Apply (SeqSym0 :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type) -> *) (l :: a6989586621679419888) Source # 
Instance details
type Apply (SeqSym0 :: TyFun a6989586621679419888 (TyFun b6989586621679419889 b6989586621679419889 -> Type) -> *) (l :: a6989586621679419888) = (SeqSym1 l :: TyFun b6989586621679419889 b6989586621679419889 -> *)

data SeqSym1 (l :: a6989586621679419888) (l :: TyFun b6989586621679419889 b6989586621679419889) Source #

Instances
SuppressUnusedWarnings (SeqSym1 :: a6989586621679419888 -> TyFun b6989586621679419889 b6989586621679419889 -> *) Source # 
Instance details
type Apply (SeqSym1 l1 :: TyFun b b -> *) (l2 :: b) Source # 
Instance details
type Apply (SeqSym1 l1 :: TyFun b b -> *) (l2 :: b) = Seq l1 l2

type SeqSym2 (t :: a6989586621679419888) (t :: b6989586621679419889) = Seq t t Source #