singletons-2.5: 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.Singletons.Prelude.Base

Contents

Description

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

Synopsis
  • type family Foldr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: b where ...
  • sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
  • type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ...
  • sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
  • type family (a :: [a]) ++ (a :: [a]) :: [a] where ...
  • (%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a])
  • type family Otherwise :: Bool where ...
  • sOtherwise :: Sing (OtherwiseSym0 :: Bool)
  • type family Id (a :: a) :: a where ...
  • sId :: forall a (t :: a). Sing t -> Sing (Apply IdSym0 t :: a)
  • type family Const (a :: a) (a :: b) :: a where ...
  • sConst :: forall a b (t :: a) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply ConstSym0 t) t :: a)
  • type family ((a :: (~>) b c) :. (a :: (~>) a b)) (a :: a) :: c where ...
  • (%.) :: forall b c a (t :: (~>) b c) (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (.@#@$) t) t) t :: c)
  • type family (a :: (~>) a b) $ (a :: a) :: b where ...
  • type family (a :: (~>) a b) $! (a :: a) :: b where ...
  • (%$) :: forall a b (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ($@#@$) t) t :: b)
  • (%$!) :: forall a b (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ($!@#@$) t) t :: b)
  • type family Until (a :: (~>) a Bool) (a :: (~>) a a) (a :: a) :: a where ...
  • sUntil :: forall a (t :: (~>) a Bool) (t :: (~>) a a) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UntilSym0 t) t) t :: a)
  • type family Flip (a :: (~>) a ((~>) b c)) (a :: b) (a :: a) :: c where ...
  • sFlip :: forall a b c (t :: (~>) a ((~>) b c)) (t :: b) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FlipSym0 t) t) t :: c)
  • type family AsTypeOf (a :: a) (a :: a) :: a where ...
  • sAsTypeOf :: forall a (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply AsTypeOfSym0 t) t :: a)
  • type family Seq (a :: a) (a :: b) :: b where ...
  • sSeq :: forall a b (t :: a) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply SeqSym0 t) t :: b)
  • data FoldrSym0 :: forall a6989586621679520929 b6989586621679520930. (~>) ((~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) ((~>) b6989586621679520930 ((~>) [a6989586621679520929] b6989586621679520930))
  • data FoldrSym1 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) :: (~>) b6989586621679520930 ((~>) [a6989586621679520929] b6989586621679520930)
  • data FoldrSym2 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) (a6989586621679521139 :: b6989586621679520930) :: (~>) [a6989586621679520929] b6989586621679520930
  • type FoldrSym3 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) (a6989586621679521139 :: b6989586621679520930) (a6989586621679521140 :: [a6989586621679520929]) = Foldr a6989586621679521138 a6989586621679521139 a6989586621679521140
  • data MapSym0 :: forall a6989586621679520927 b6989586621679520928. (~>) ((~>) a6989586621679520927 b6989586621679520928) ((~>) [a6989586621679520927] [b6989586621679520928])
  • data MapSym1 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) :: (~>) [a6989586621679520927] [b6989586621679520928]
  • type MapSym2 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) (a6989586621679521132 :: [a6989586621679520927]) = Map a6989586621679521131 a6989586621679521132
  • data (++@#@$) :: forall a6989586621679520926. (~>) [a6989586621679520926] ((~>) [a6989586621679520926] [a6989586621679520926])
  • data (++@#@$$) (a6989586621679521123 :: [a6989586621679520926]) :: (~>) [a6989586621679520926] [a6989586621679520926]
  • type (++@#@$$$) (a6989586621679521123 :: [a6989586621679520926]) (a6989586621679521124 :: [a6989586621679520926]) = (++) a6989586621679521123 a6989586621679521124
  • type OtherwiseSym0 = Otherwise
  • data IdSym0 :: forall a6989586621679520925. (~>) a6989586621679520925 a6989586621679520925
  • type IdSym1 (a6989586621679521120 :: a6989586621679520925) = Id a6989586621679521120
  • data ConstSym0 :: forall a6989586621679520923 b6989586621679520924. (~>) a6989586621679520923 ((~>) b6989586621679520924 a6989586621679520923)
  • data ConstSym1 (a6989586621679521105 :: a6989586621679520923) :: forall b6989586621679520924. (~>) b6989586621679520924 a6989586621679520923
  • type ConstSym2 (a6989586621679521105 :: a6989586621679520923) (a6989586621679521106 :: b6989586621679520924) = Const a6989586621679521105 a6989586621679521106
  • data (.@#@$) :: forall a6989586621679520922 b6989586621679520920 c6989586621679520921. (~>) ((~>) b6989586621679520920 c6989586621679520921) ((~>) ((~>) a6989586621679520922 b6989586621679520920) ((~>) a6989586621679520922 c6989586621679520921))
  • data (.@#@$$) (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) :: forall a6989586621679520922. (~>) ((~>) a6989586621679520922 b6989586621679520920) ((~>) a6989586621679520922 c6989586621679520921)
  • data (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) .@#@$$$ (a6989586621679521087 :: (~>) a6989586621679520922 b6989586621679520920) :: (~>) a6989586621679520922 c6989586621679520921
  • type (.@#@$$$$) (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) (a6989586621679521087 :: (~>) a6989586621679520922 b6989586621679520920) (a6989586621679521088 :: a6989586621679520922) = (:.) a6989586621679521086 a6989586621679521087 a6989586621679521088
  • data ($@#@$) :: forall a6989586621679520914 b6989586621679520915. (~>) ((~>) a6989586621679520914 b6989586621679520915) ((~>) a6989586621679520914 b6989586621679520915)
  • data ($@#@$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) :: (~>) a6989586621679520914 b6989586621679520915
  • type ($@#@$$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) (a6989586621679521072 :: a6989586621679520914) = ($) a6989586621679521071 a6989586621679521072
  • data ($!@#@$) :: forall a6989586621679520912 b6989586621679520913. (~>) ((~>) a6989586621679520912 b6989586621679520913) ((~>) a6989586621679520912 b6989586621679520913)
  • data ($!@#@$$) (a6989586621679521062 :: (~>) a6989586621679520912 b6989586621679520913) :: (~>) a6989586621679520912 b6989586621679520913
  • type ($!@#@$$$) (a6989586621679521062 :: (~>) a6989586621679520912 b6989586621679520913) (a6989586621679521063 :: a6989586621679520912) = ($!) a6989586621679521062 a6989586621679521063
  • data UntilSym0 :: forall a6989586621679520911. (~>) ((~>) a6989586621679520911 Bool) ((~>) ((~>) a6989586621679520911 a6989586621679520911) ((~>) a6989586621679520911 a6989586621679520911))
  • data UntilSym1 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) :: (~>) ((~>) a6989586621679520911 a6989586621679520911) ((~>) a6989586621679520911 a6989586621679520911)
  • data UntilSym2 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) (a6989586621679521037 :: (~>) a6989586621679520911 a6989586621679520911) :: (~>) a6989586621679520911 a6989586621679520911
  • type UntilSym3 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) (a6989586621679521037 :: (~>) a6989586621679520911 a6989586621679520911) (a6989586621679521038 :: a6989586621679520911) = Until a6989586621679521036 a6989586621679521037 a6989586621679521038
  • data FlipSym0 :: forall a6989586621679520917 b6989586621679520918 c6989586621679520919. (~>) ((~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) ((~>) b6989586621679520918 ((~>) a6989586621679520917 c6989586621679520919))
  • data FlipSym1 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) :: (~>) b6989586621679520918 ((~>) a6989586621679520917 c6989586621679520919)
  • data FlipSym2 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) (a6989586621679521078 :: b6989586621679520918) :: (~>) a6989586621679520917 c6989586621679520919
  • type FlipSym3 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) (a6989586621679521078 :: b6989586621679520918) (a6989586621679521079 :: a6989586621679520917) = Flip a6989586621679521077 a6989586621679521078 a6989586621679521079
  • data AsTypeOfSym0 :: forall a6989586621679520916. (~>) a6989586621679520916 ((~>) a6989586621679520916 a6989586621679520916)
  • data AsTypeOfSym1 (a6989586621679521114 :: a6989586621679520916) :: (~>) a6989586621679520916 a6989586621679520916
  • type AsTypeOfSym2 (a6989586621679521114 :: a6989586621679520916) (a6989586621679521115 :: a6989586621679520916) = AsTypeOf a6989586621679521114 a6989586621679521115
  • data SeqSym0 :: forall a6989586621679520909 b6989586621679520910. (~>) a6989586621679520909 ((~>) b6989586621679520910 b6989586621679520910)
  • data SeqSym1 (a6989586621679521031 :: a6989586621679520909) :: forall b6989586621679520910. (~>) b6989586621679520910 b6989586621679520910
  • type SeqSym2 (a6989586621679521031 :: a6989586621679520909) (a6989586621679521032 :: b6989586621679520910) = Seq a6989586621679521031 a6989586621679521032

Basic functions

type family Foldr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: b where ... Source #

Equations

Foldr k z a_6989586621679521144 = Apply (Let6989586621679521149GoSym3 k z a_6989586621679521144) a_6989586621679521144 

sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

type family Map (a :: (~>) a b) (a :: [a]) :: [b] where ... Source #

Equations

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

sMap :: forall a b (t :: (~>) a b) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b]) Source #

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

Equations

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

(%++) :: forall a (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (++@#@$) t) t :: [a]) infixr 5 Source #

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

Equations

Otherwise = TrueSym0 

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

Equations

Id x = x 

sId :: forall a (t :: a). Sing t -> Sing (Apply IdSym0 t :: a) Source #

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

Equations

Const x _ = x 

sConst :: forall a b (t :: a) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply ConstSym0 t) t :: a) Source #

type family ((a :: (~>) b c) :. (a :: (~>) a b)) (a :: a) :: c where ... infixr 9 Source #

Equations

(f :. g) a_6989586621679521092 = Apply (Apply (Apply (Apply Lambda_6989586621679521097Sym0 f) g) a_6989586621679521092) a_6989586621679521092 

(%.) :: forall b c a (t :: (~>) b c) (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (.@#@$) t) t) t :: c) infixr 9 Source #

type family (a :: (~>) a b) $ (a :: a) :: b where ... infixr 0 Source #

Equations

f $ x = Apply f x 

type family (a :: (~>) a b) $! (a :: a) :: b where ... infixr 0 Source #

Equations

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

(%$) :: forall a b (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ($@#@$) t) t :: b) infixr 0 Source #

(%$!) :: forall a b (t :: (~>) a b) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply ($!@#@$) t) t :: b) infixr 0 Source #

type family Until (a :: (~>) a Bool) (a :: (~>) a a) (a :: a) :: a where ... Source #

Equations

Until p f a_6989586621679521042 = Apply (Let6989586621679521047GoSym3 p f a_6989586621679521042) a_6989586621679521042 

sUntil :: forall a (t :: (~>) a Bool) (t :: (~>) a a) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UntilSym0 t) t) t :: a) Source #

type family Flip (a :: (~>) a ((~>) b c)) (a :: b) (a :: a) :: c where ... Source #

Equations

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

sFlip :: forall a b c (t :: (~>) a ((~>) b c)) (t :: b) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FlipSym0 t) t) t :: c) Source #

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

Equations

AsTypeOf a_6989586621679521110 a_6989586621679521112 = Apply (Apply ConstSym0 a_6989586621679521110) a_6989586621679521112 

sAsTypeOf :: forall a (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply AsTypeOfSym0 t) t :: a) Source #

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

Equations

Seq _ x = x 

sSeq :: forall a b (t :: a) (t :: b). Sing t -> Sing t -> Sing (Apply (Apply SeqSym0 t) t :: b) infixr 0 Source #

Defunctionalization symbols

data FoldrSym0 :: forall a6989586621679520929 b6989586621679520930. (~>) ((~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) ((~>) b6989586621679520930 ((~>) [a6989586621679520929] b6989586621679520930)) Source #

Instances
SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FoldrSym0 :: TyFun (a6989586621679520929 ~> (b6989586621679520930 ~> b6989586621679520930)) (b6989586621679520930 ~> ([a6989586621679520929] ~> b6989586621679520930)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (a6989586621679520929 ~> (b6989586621679520930 ~> b6989586621679520930)) (b6989586621679520930 ~> ([a6989586621679520929] ~> b6989586621679520930)) -> Type) (a6989586621679521138 :: a6989586621679520929 ~> (b6989586621679520930 ~> b6989586621679520930)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (a6989586621679520929 ~> (b6989586621679520930 ~> b6989586621679520930)) (b6989586621679520930 ~> ([a6989586621679520929] ~> b6989586621679520930)) -> Type) (a6989586621679521138 :: a6989586621679520929 ~> (b6989586621679520930 ~> b6989586621679520930)) = FoldrSym1 a6989586621679521138

data FoldrSym1 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) :: (~>) b6989586621679520930 ((~>) [a6989586621679520929] b6989586621679520930) Source #

Instances
SingI d => SingI (FoldrSym1 d :: TyFun b ([a] ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (FoldrSym1 d) Source #

SuppressUnusedWarnings (FoldrSym1 a6989586621679521138 :: TyFun b6989586621679520930 ([a6989586621679520929] ~> b6989586621679520930) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 a6989586621679521138 :: TyFun b6989586621679520930 ([a6989586621679520929] ~> b6989586621679520930) -> Type) (a6989586621679521139 :: b6989586621679520930) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 a6989586621679521138 :: TyFun b6989586621679520930 ([a6989586621679520929] ~> b6989586621679520930) -> Type) (a6989586621679521139 :: b6989586621679520930) = FoldrSym2 a6989586621679521138 a6989586621679521139

data FoldrSym2 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) (a6989586621679521139 :: b6989586621679520930) :: (~>) [a6989586621679520929] b6989586621679520930 Source #

Instances
(SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun [a] b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (FoldrSym2 d1 d2) Source #

SuppressUnusedWarnings (FoldrSym2 a6989586621679521139 a6989586621679521138 :: TyFun [a6989586621679520929] b6989586621679520930 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 a6989586621679521139 a6989586621679521138 :: TyFun [a] b -> Type) (a6989586621679521140 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 a6989586621679521139 a6989586621679521138 :: TyFun [a] b -> Type) (a6989586621679521140 :: [a]) = Foldr a6989586621679521139 a6989586621679521138 a6989586621679521140

type FoldrSym3 (a6989586621679521138 :: (~>) a6989586621679520929 ((~>) b6989586621679520930 b6989586621679520930)) (a6989586621679521139 :: b6989586621679520930) (a6989586621679521140 :: [a6989586621679520929]) = Foldr a6989586621679521138 a6989586621679521139 a6989586621679521140 Source #

data MapSym0 :: forall a6989586621679520927 b6989586621679520928. (~>) ((~>) a6989586621679520927 b6989586621679520928) ((~>) [a6989586621679520927] [b6989586621679520928]) Source #

Instances
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) (a6989586621679521131 :: a6989586621679520927 ~> b6989586621679520928) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679520927 ~> b6989586621679520928) ([a6989586621679520927] ~> [b6989586621679520928]) -> Type) (a6989586621679521131 :: a6989586621679520927 ~> b6989586621679520928) = MapSym1 a6989586621679521131

data MapSym1 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) :: (~>) [a6989586621679520927] [b6989586621679520928] Source #

Instances
SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (MapSym1 d) Source #

SuppressUnusedWarnings (MapSym1 a6989586621679521131 :: TyFun [a6989586621679520927] [b6989586621679520928] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 a6989586621679521131 :: TyFun [a] [b] -> Type) (a6989586621679521132 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym1 a6989586621679521131 :: TyFun [a] [b] -> Type) (a6989586621679521132 :: [a]) = Map a6989586621679521131 a6989586621679521132

type MapSym2 (a6989586621679521131 :: (~>) a6989586621679520927 b6989586621679520928) (a6989586621679521132 :: [a6989586621679520927]) = Map a6989586621679521131 a6989586621679521132 Source #

data (++@#@$) :: forall a6989586621679520926. (~>) [a6989586621679520926] ((~>) [a6989586621679520926] [a6989586621679520926]) infixr 5 Source #

Instances
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) (a6989586621679521123 :: [a6989586621679520926]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$) :: TyFun [a6989586621679520926] ([a6989586621679520926] ~> [a6989586621679520926]) -> Type) (a6989586621679521123 :: [a6989586621679520926]) = (++@#@$$) a6989586621679521123

data (++@#@$$) (a6989586621679521123 :: [a6989586621679520926]) :: (~>) [a6989586621679520926] [a6989586621679520926] infixr 5 Source #

Instances
SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing ((++@#@$$) d) Source #

SuppressUnusedWarnings ((++@#@$$) a6989586621679521123 :: TyFun [a6989586621679520926] [a6989586621679520926] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) a6989586621679521123 :: TyFun [a] [a] -> Type) (a6989586621679521124 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((++@#@$$) a6989586621679521123 :: TyFun [a] [a] -> Type) (a6989586621679521124 :: [a]) = a6989586621679521123 ++ a6989586621679521124

type (++@#@$$$) (a6989586621679521123 :: [a6989586621679520926]) (a6989586621679521124 :: [a6989586621679520926]) = (++) a6989586621679521123 a6989586621679521124 Source #

data IdSym0 :: forall a6989586621679520925. (~>) a6989586621679520925 a6989586621679520925 Source #

Instances
SingI (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing IdSym0 Source #

SuppressUnusedWarnings (IdSym0 :: TyFun a6989586621679520925 a6989586621679520925 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679521120 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679521120 :: a) = Id a6989586621679521120

type IdSym1 (a6989586621679521120 :: a6989586621679520925) = Id a6989586621679521120 Source #

data ConstSym0 :: forall a6989586621679520923 b6989586621679520924. (~>) a6989586621679520923 ((~>) b6989586621679520924 a6989586621679520923) Source #

Instances
SingI (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ConstSym0 :: TyFun a6989586621679520923 (b6989586621679520924 ~> a6989586621679520923) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym0 :: TyFun a6989586621679520923 (b6989586621679520924 ~> a6989586621679520923) -> Type) (a6989586621679521105 :: a6989586621679520923) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym0 :: TyFun a6989586621679520923 (b6989586621679520924 ~> a6989586621679520923) -> Type) (a6989586621679521105 :: a6989586621679520923) = (ConstSym1 a6989586621679521105 b6989586621679520924 :: TyFun b6989586621679520924 a6989586621679520923 -> Type)

data ConstSym1 (a6989586621679521105 :: a6989586621679520923) :: forall b6989586621679520924. (~>) b6989586621679520924 a6989586621679520923 Source #

Instances
SingI d => SingI (ConstSym1 d b :: TyFun b a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (ConstSym1 d b) Source #

SuppressUnusedWarnings (ConstSym1 a6989586621679521105 b6989586621679520924 :: TyFun b6989586621679520924 a6989586621679520923 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym1 a6989586621679521105 b :: TyFun b a -> Type) (a6989586621679521106 :: b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym1 a6989586621679521105 b :: TyFun b a -> Type) (a6989586621679521106 :: b) = Const a6989586621679521105 a6989586621679521106

type ConstSym2 (a6989586621679521105 :: a6989586621679520923) (a6989586621679521106 :: b6989586621679520924) = Const a6989586621679521105 a6989586621679521106 Source #

data (.@#@$) :: forall a6989586621679520922 b6989586621679520920 c6989586621679520921. (~>) ((~>) b6989586621679520920 c6989586621679520921) ((~>) ((~>) a6989586621679520922 b6989586621679520920) ((~>) a6989586621679520922 c6989586621679520921)) infixr 9 Source #

Instances
SingI ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((.@#@$) :: TyFun (b6989586621679520920 ~> c6989586621679520921) ((a6989586621679520922 ~> b6989586621679520920) ~> (a6989586621679520922 ~> c6989586621679520921)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (b6989586621679520920 ~> c6989586621679520921) ((a6989586621679520922 ~> b6989586621679520920) ~> (a6989586621679520922 ~> c6989586621679520921)) -> Type) (a6989586621679521086 :: b6989586621679520920 ~> c6989586621679520921) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (b6989586621679520920 ~> c6989586621679520921) ((a6989586621679520922 ~> b6989586621679520920) ~> (a6989586621679520922 ~> c6989586621679520921)) -> Type) (a6989586621679521086 :: b6989586621679520920 ~> c6989586621679520921) = (a6989586621679521086 .@#@$$ a6989586621679520922 :: TyFun (a6989586621679520922 ~> b6989586621679520920) (a6989586621679520922 ~> c6989586621679520921) -> Type)

data (.@#@$$) (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) :: forall a6989586621679520922. (~>) ((~>) a6989586621679520922 b6989586621679520920) ((~>) a6989586621679520922 c6989586621679520921) infixr 9 Source #

Instances
SingI d => SingI (d .@#@$$ a :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (d .@#@$$ a) Source #

SuppressUnusedWarnings (a6989586621679521086 .@#@$$ a6989586621679520922 :: TyFun (a6989586621679520922 ~> b6989586621679520920) (a6989586621679520922 ~> c6989586621679520921) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521086 .@#@$$ a6989586621679520922 :: TyFun (a6989586621679520922 ~> b6989586621679520920) (a6989586621679520922 ~> c6989586621679520921) -> Type) (a6989586621679521087 :: a6989586621679520922 ~> b6989586621679520920) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521086 .@#@$$ a6989586621679520922 :: TyFun (a6989586621679520922 ~> b6989586621679520920) (a6989586621679520922 ~> c6989586621679520921) -> Type) (a6989586621679521087 :: a6989586621679520922 ~> b6989586621679520920) = a6989586621679521086 .@#@$$$ a6989586621679521087

data (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) .@#@$$$ (a6989586621679521087 :: (~>) a6989586621679520922 b6989586621679520920) :: (~>) a6989586621679520922 c6989586621679520921 infixr 9 Source #

Instances
(SingI d1, SingI d2) => SingI (d1 .@#@$$$ d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (d1 .@#@$$$ d2) Source #

SuppressUnusedWarnings (a6989586621679521087 .@#@$$$ a6989586621679521086 :: TyFun a6989586621679520922 c6989586621679520921 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521087 .@#@$$$ a6989586621679521086 :: TyFun a c -> Type) (a6989586621679521088 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521087 .@#@$$$ a6989586621679521086 :: TyFun a c -> Type) (a6989586621679521088 :: a) = (a6989586621679521087 :. a6989586621679521086) a6989586621679521088

type (.@#@$$$$) (a6989586621679521086 :: (~>) b6989586621679520920 c6989586621679520921) (a6989586621679521087 :: (~>) a6989586621679520922 b6989586621679520920) (a6989586621679521088 :: a6989586621679520922) = (:.) a6989586621679521086 a6989586621679521087 a6989586621679521088 Source #

data ($@#@$) :: forall a6989586621679520914 b6989586621679520915. (~>) ((~>) a6989586621679520914 b6989586621679520915) ((~>) a6989586621679520914 b6989586621679520915) infixr 0 Source #

Instances
SingI (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (($@#@$) :: TyFun (a6989586621679520914 ~> b6989586621679520915) (a6989586621679520914 ~> b6989586621679520915) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$) :: TyFun (a6989586621679520914 ~> b6989586621679520915) (a6989586621679520914 ~> b6989586621679520915) -> Type) (a6989586621679521071 :: a6989586621679520914 ~> b6989586621679520915) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$) :: TyFun (a6989586621679520914 ~> b6989586621679520915) (a6989586621679520914 ~> b6989586621679520915) -> Type) (a6989586621679521071 :: a6989586621679520914 ~> b6989586621679520915) = ($@#@$$) a6989586621679521071

data ($@#@$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) :: (~>) a6989586621679520914 b6989586621679520915 infixr 0 Source #

Instances
SingI d => SingI (($@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (($@#@$$) d) Source #

SuppressUnusedWarnings (($@#@$$) a6989586621679521071 :: TyFun a6989586621679520914 b6989586621679520915 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$$) a6989586621679521071 :: TyFun a b -> Type) (a6989586621679521072 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$$) a6989586621679521071 :: TyFun a b -> Type) (a6989586621679521072 :: a) = a6989586621679521071 $ a6989586621679521072

type ($@#@$$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) (a6989586621679521072 :: a6989586621679520914) = ($) a6989586621679521071 a6989586621679521072 Source #

data ($!@#@$) :: forall a6989586621679520912 b6989586621679520913. (~>) ((~>) a6989586621679520912 b6989586621679520913) ((~>) a6989586621679520912 b6989586621679520913) infixr 0 Source #

Instances
SingI (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (($!@#@$) :: TyFun (a6989586621679520912 ~> b6989586621679520913) (a6989586621679520912 ~> b6989586621679520913) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$) :: TyFun (a6989586621679520912 ~> b6989586621679520913) (a6989586621679520912 ~> b6989586621679520913) -> Type) (a6989586621679521062 :: a6989586621679520912 ~> b6989586621679520913) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$) :: TyFun (a6989586621679520912 ~> b6989586621679520913) (a6989586621679520912 ~> b6989586621679520913) -> Type) (a6989586621679521062 :: a6989586621679520912 ~> b6989586621679520913) = ($!@#@$$) a6989586621679521062

data ($!@#@$$) (a6989586621679521062 :: (~>) a6989586621679520912 b6989586621679520913) :: (~>) a6989586621679520912 b6989586621679520913 infixr 0 Source #

Instances
SingI d => SingI (($!@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (($!@#@$$) d) Source #

SuppressUnusedWarnings (($!@#@$$) a6989586621679521062 :: TyFun a6989586621679520912 b6989586621679520913 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$$) a6989586621679521062 :: TyFun a b -> Type) (a6989586621679521063 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$$) a6989586621679521062 :: TyFun a b -> Type) (a6989586621679521063 :: a) = a6989586621679521062 $! a6989586621679521063

type ($!@#@$$$) (a6989586621679521062 :: (~>) a6989586621679520912 b6989586621679520913) (a6989586621679521063 :: a6989586621679520912) = ($!) a6989586621679521062 a6989586621679521063 Source #

data UntilSym0 :: forall a6989586621679520911. (~>) ((~>) a6989586621679520911 Bool) ((~>) ((~>) a6989586621679520911 a6989586621679520911) ((~>) a6989586621679520911 a6989586621679520911)) Source #

Instances
SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (UntilSym0 :: TyFun (a6989586621679520911 ~> Bool) ((a6989586621679520911 ~> a6989586621679520911) ~> (a6989586621679520911 ~> a6989586621679520911)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679520911 ~> Bool) ((a6989586621679520911 ~> a6989586621679520911) ~> (a6989586621679520911 ~> a6989586621679520911)) -> Type) (a6989586621679521036 :: a6989586621679520911 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679520911 ~> Bool) ((a6989586621679520911 ~> a6989586621679520911) ~> (a6989586621679520911 ~> a6989586621679520911)) -> Type) (a6989586621679521036 :: a6989586621679520911 ~> Bool) = UntilSym1 a6989586621679521036

data UntilSym1 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) :: (~>) ((~>) a6989586621679520911 a6989586621679520911) ((~>) a6989586621679520911 a6989586621679520911) Source #

Instances
SingI d => SingI (UntilSym1 d :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (UntilSym1 d) Source #

SuppressUnusedWarnings (UntilSym1 a6989586621679521036 :: TyFun (a6989586621679520911 ~> a6989586621679520911) (a6989586621679520911 ~> a6989586621679520911) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym1 a6989586621679521036 :: TyFun (a6989586621679520911 ~> a6989586621679520911) (a6989586621679520911 ~> a6989586621679520911) -> Type) (a6989586621679521037 :: a6989586621679520911 ~> a6989586621679520911) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym1 a6989586621679521036 :: TyFun (a6989586621679520911 ~> a6989586621679520911) (a6989586621679520911 ~> a6989586621679520911) -> Type) (a6989586621679521037 :: a6989586621679520911 ~> a6989586621679520911) = UntilSym2 a6989586621679521036 a6989586621679521037

data UntilSym2 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) (a6989586621679521037 :: (~>) a6989586621679520911 a6989586621679520911) :: (~>) a6989586621679520911 a6989586621679520911 Source #

Instances
(SingI d1, SingI d2) => SingI (UntilSym2 d1 d2 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (UntilSym2 d1 d2) Source #

SuppressUnusedWarnings (UntilSym2 a6989586621679521037 a6989586621679521036 :: TyFun a6989586621679520911 a6989586621679520911 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym2 a6989586621679521037 a6989586621679521036 :: TyFun a a -> Type) (a6989586621679521038 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym2 a6989586621679521037 a6989586621679521036 :: TyFun a a -> Type) (a6989586621679521038 :: a) = Until a6989586621679521037 a6989586621679521036 a6989586621679521038

type UntilSym3 (a6989586621679521036 :: (~>) a6989586621679520911 Bool) (a6989586621679521037 :: (~>) a6989586621679520911 a6989586621679520911) (a6989586621679521038 :: a6989586621679520911) = Until a6989586621679521036 a6989586621679521037 a6989586621679521038 Source #

data FlipSym0 :: forall a6989586621679520917 b6989586621679520918 c6989586621679520919. (~>) ((~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) ((~>) b6989586621679520918 ((~>) a6989586621679520917 c6989586621679520919)) Source #

Instances
SingI (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FlipSym0 :: TyFun (a6989586621679520917 ~> (b6989586621679520918 ~> c6989586621679520919)) (b6989586621679520918 ~> (a6989586621679520917 ~> c6989586621679520919)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym0 :: TyFun (a6989586621679520917 ~> (b6989586621679520918 ~> c6989586621679520919)) (b6989586621679520918 ~> (a6989586621679520917 ~> c6989586621679520919)) -> Type) (a6989586621679521077 :: a6989586621679520917 ~> (b6989586621679520918 ~> c6989586621679520919)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym0 :: TyFun (a6989586621679520917 ~> (b6989586621679520918 ~> c6989586621679520919)) (b6989586621679520918 ~> (a6989586621679520917 ~> c6989586621679520919)) -> Type) (a6989586621679521077 :: a6989586621679520917 ~> (b6989586621679520918 ~> c6989586621679520919)) = FlipSym1 a6989586621679521077

data FlipSym1 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) :: (~>) b6989586621679520918 ((~>) a6989586621679520917 c6989586621679520919) Source #

Instances
SingI d => SingI (FlipSym1 d :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (FlipSym1 d) Source #

SuppressUnusedWarnings (FlipSym1 a6989586621679521077 :: TyFun b6989586621679520918 (a6989586621679520917 ~> c6989586621679520919) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym1 a6989586621679521077 :: TyFun b6989586621679520918 (a6989586621679520917 ~> c6989586621679520919) -> Type) (a6989586621679521078 :: b6989586621679520918) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym1 a6989586621679521077 :: TyFun b6989586621679520918 (a6989586621679520917 ~> c6989586621679520919) -> Type) (a6989586621679521078 :: b6989586621679520918) = FlipSym2 a6989586621679521077 a6989586621679521078

data FlipSym2 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) (a6989586621679521078 :: b6989586621679520918) :: (~>) a6989586621679520917 c6989586621679520919 Source #

Instances
(SingI d1, SingI d2) => SingI (FlipSym2 d1 d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (FlipSym2 d1 d2) Source #

SuppressUnusedWarnings (FlipSym2 a6989586621679521078 a6989586621679521077 :: TyFun a6989586621679520917 c6989586621679520919 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym2 a6989586621679521078 a6989586621679521077 :: TyFun a c -> Type) (a6989586621679521079 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym2 a6989586621679521078 a6989586621679521077 :: TyFun a c -> Type) (a6989586621679521079 :: a) = Flip a6989586621679521078 a6989586621679521077 a6989586621679521079

type FlipSym3 (a6989586621679521077 :: (~>) a6989586621679520917 ((~>) b6989586621679520918 c6989586621679520919)) (a6989586621679521078 :: b6989586621679520918) (a6989586621679521079 :: a6989586621679520917) = Flip a6989586621679521077 a6989586621679521078 a6989586621679521079 Source #

data AsTypeOfSym0 :: forall a6989586621679520916. (~>) a6989586621679520916 ((~>) a6989586621679520916 a6989586621679520916) Source #

Instances
SingI (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a6989586621679520916 (a6989586621679520916 ~> a6989586621679520916) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym0 :: TyFun a6989586621679520916 (a6989586621679520916 ~> a6989586621679520916) -> Type) (a6989586621679521114 :: a6989586621679520916) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym0 :: TyFun a6989586621679520916 (a6989586621679520916 ~> a6989586621679520916) -> Type) (a6989586621679521114 :: a6989586621679520916) = AsTypeOfSym1 a6989586621679521114

data AsTypeOfSym1 (a6989586621679521114 :: a6989586621679520916) :: (~>) a6989586621679520916 a6989586621679520916 Source #

Instances
SingI d => SingI (AsTypeOfSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (AsTypeOfSym1 d) Source #

SuppressUnusedWarnings (AsTypeOfSym1 a6989586621679521114 :: TyFun a6989586621679520916 a6989586621679520916 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym1 a6989586621679521114 :: TyFun a a -> Type) (a6989586621679521115 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym1 a6989586621679521114 :: TyFun a a -> Type) (a6989586621679521115 :: a) = AsTypeOf a6989586621679521114 a6989586621679521115

type AsTypeOfSym2 (a6989586621679521114 :: a6989586621679520916) (a6989586621679521115 :: a6989586621679520916) = AsTypeOf a6989586621679521114 a6989586621679521115 Source #

data SeqSym0 :: forall a6989586621679520909 b6989586621679520910. (~>) a6989586621679520909 ((~>) b6989586621679520910 b6989586621679520910) infixr 0 Source #

Instances
SingI (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (SeqSym0 :: TyFun a6989586621679520909 (b6989586621679520910 ~> b6989586621679520910) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym0 :: TyFun a6989586621679520909 (b6989586621679520910 ~> b6989586621679520910) -> Type) (a6989586621679521031 :: a6989586621679520909) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym0 :: TyFun a6989586621679520909 (b6989586621679520910 ~> b6989586621679520910) -> Type) (a6989586621679521031 :: a6989586621679520909) = (SeqSym1 a6989586621679521031 b6989586621679520910 :: TyFun b6989586621679520910 b6989586621679520910 -> Type)

data SeqSym1 (a6989586621679521031 :: a6989586621679520909) :: forall b6989586621679520910. (~>) b6989586621679520910 b6989586621679520910 infixr 0 Source #

Instances
SingI d => SingI (SeqSym1 d b :: TyFun b b -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing (SeqSym1 d b) Source #

SuppressUnusedWarnings (SeqSym1 a6989586621679521031 b6989586621679520910 :: TyFun b6989586621679520910 b6989586621679520910 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym1 a6989586621679521031 b :: TyFun b b -> Type) (a6989586621679521032 :: b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym1 a6989586621679521031 b :: TyFun b b -> Type) (a6989586621679521032 :: b) = Seq a6989586621679521031 a6989586621679521032

type SeqSym2 (a6989586621679521031 :: a6989586621679520909) (a6989586621679521032 :: b6989586621679520910) = Seq a6989586621679521031 a6989586621679521032 Source #