singletons-2.5.1: 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 a6989586621679521718 b6989586621679521719. (~>) ((~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) ((~>) b6989586621679521719 ((~>) [a6989586621679521718] b6989586621679521719))
  • data FoldrSym1 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) :: (~>) b6989586621679521719 ((~>) [a6989586621679521718] b6989586621679521719)
  • data FoldrSym2 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) (a6989586621679521928 :: b6989586621679521719) :: (~>) [a6989586621679521718] b6989586621679521719
  • type FoldrSym3 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) (a6989586621679521928 :: b6989586621679521719) (a6989586621679521929 :: [a6989586621679521718]) = Foldr a6989586621679521927 a6989586621679521928 a6989586621679521929
  • data MapSym0 :: forall a6989586621679521716 b6989586621679521717. (~>) ((~>) a6989586621679521716 b6989586621679521717) ((~>) [a6989586621679521716] [b6989586621679521717])
  • data MapSym1 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) :: (~>) [a6989586621679521716] [b6989586621679521717]
  • type MapSym2 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) (a6989586621679521921 :: [a6989586621679521716]) = Map a6989586621679521920 a6989586621679521921
  • data (++@#@$) :: forall a6989586621679521715. (~>) [a6989586621679521715] ((~>) [a6989586621679521715] [a6989586621679521715])
  • data (++@#@$$) (a6989586621679521912 :: [a6989586621679521715]) :: (~>) [a6989586621679521715] [a6989586621679521715]
  • type (++@#@$$$) (a6989586621679521912 :: [a6989586621679521715]) (a6989586621679521913 :: [a6989586621679521715]) = (++) a6989586621679521912 a6989586621679521913
  • type OtherwiseSym0 = Otherwise
  • data IdSym0 :: forall a6989586621679521714. (~>) a6989586621679521714 a6989586621679521714
  • type IdSym1 (a6989586621679521909 :: a6989586621679521714) = Id a6989586621679521909
  • data ConstSym0 :: forall a6989586621679521712 b6989586621679521713. (~>) a6989586621679521712 ((~>) b6989586621679521713 a6989586621679521712)
  • data ConstSym1 (a6989586621679521894 :: a6989586621679521712) :: forall b6989586621679521713. (~>) b6989586621679521713 a6989586621679521712
  • type ConstSym2 (a6989586621679521894 :: a6989586621679521712) (a6989586621679521895 :: b6989586621679521713) = Const a6989586621679521894 a6989586621679521895
  • data (.@#@$) :: forall a6989586621679521711 b6989586621679521709 c6989586621679521710. (~>) ((~>) b6989586621679521709 c6989586621679521710) ((~>) ((~>) a6989586621679521711 b6989586621679521709) ((~>) a6989586621679521711 c6989586621679521710))
  • data (.@#@$$) (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) :: forall a6989586621679521711. (~>) ((~>) a6989586621679521711 b6989586621679521709) ((~>) a6989586621679521711 c6989586621679521710)
  • data (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) .@#@$$$ (a6989586621679521876 :: (~>) a6989586621679521711 b6989586621679521709) :: (~>) a6989586621679521711 c6989586621679521710
  • type (.@#@$$$$) (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) (a6989586621679521876 :: (~>) a6989586621679521711 b6989586621679521709) (a6989586621679521877 :: a6989586621679521711) = (:.) a6989586621679521875 a6989586621679521876 a6989586621679521877
  • data ($@#@$) :: forall a6989586621679521703 b6989586621679521704. (~>) ((~>) a6989586621679521703 b6989586621679521704) ((~>) a6989586621679521703 b6989586621679521704)
  • data ($@#@$$) (a6989586621679521860 :: (~>) a6989586621679521703 b6989586621679521704) :: (~>) a6989586621679521703 b6989586621679521704
  • type ($@#@$$$) (a6989586621679521860 :: (~>) a6989586621679521703 b6989586621679521704) (a6989586621679521861 :: a6989586621679521703) = ($) a6989586621679521860 a6989586621679521861
  • data ($!@#@$) :: forall a6989586621679521701 b6989586621679521702. (~>) ((~>) a6989586621679521701 b6989586621679521702) ((~>) a6989586621679521701 b6989586621679521702)
  • data ($!@#@$$) (a6989586621679521851 :: (~>) a6989586621679521701 b6989586621679521702) :: (~>) a6989586621679521701 b6989586621679521702
  • type ($!@#@$$$) (a6989586621679521851 :: (~>) a6989586621679521701 b6989586621679521702) (a6989586621679521852 :: a6989586621679521701) = ($!) a6989586621679521851 a6989586621679521852
  • data UntilSym0 :: forall a6989586621679521700. (~>) ((~>) a6989586621679521700 Bool) ((~>) ((~>) a6989586621679521700 a6989586621679521700) ((~>) a6989586621679521700 a6989586621679521700))
  • data UntilSym1 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) :: (~>) ((~>) a6989586621679521700 a6989586621679521700) ((~>) a6989586621679521700 a6989586621679521700)
  • data UntilSym2 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) (a6989586621679521826 :: (~>) a6989586621679521700 a6989586621679521700) :: (~>) a6989586621679521700 a6989586621679521700
  • type UntilSym3 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) (a6989586621679521826 :: (~>) a6989586621679521700 a6989586621679521700) (a6989586621679521827 :: a6989586621679521700) = Until a6989586621679521825 a6989586621679521826 a6989586621679521827
  • data FlipSym0 :: forall a6989586621679521706 b6989586621679521707 c6989586621679521708. (~>) ((~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) ((~>) b6989586621679521707 ((~>) a6989586621679521706 c6989586621679521708))
  • data FlipSym1 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) :: (~>) b6989586621679521707 ((~>) a6989586621679521706 c6989586621679521708)
  • data FlipSym2 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) (a6989586621679521867 :: b6989586621679521707) :: (~>) a6989586621679521706 c6989586621679521708
  • type FlipSym3 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) (a6989586621679521867 :: b6989586621679521707) (a6989586621679521868 :: a6989586621679521706) = Flip a6989586621679521866 a6989586621679521867 a6989586621679521868
  • data AsTypeOfSym0 :: forall a6989586621679521705. (~>) a6989586621679521705 ((~>) a6989586621679521705 a6989586621679521705)
  • data AsTypeOfSym1 (a6989586621679521903 :: a6989586621679521705) :: (~>) a6989586621679521705 a6989586621679521705
  • type AsTypeOfSym2 (a6989586621679521903 :: a6989586621679521705) (a6989586621679521904 :: a6989586621679521705) = AsTypeOf a6989586621679521903 a6989586621679521904
  • data SeqSym0 :: forall a6989586621679521698 b6989586621679521699. (~>) a6989586621679521698 ((~>) b6989586621679521699 b6989586621679521699)
  • data SeqSym1 (a6989586621679521820 :: a6989586621679521698) :: forall b6989586621679521699. (~>) b6989586621679521699 b6989586621679521699
  • type SeqSym2 (a6989586621679521820 :: a6989586621679521698) (a6989586621679521821 :: b6989586621679521699) = Seq a6989586621679521820 a6989586621679521821

Basic functions

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

Equations

Foldr k z a_6989586621679521933 = Apply (Let6989586621679521938GoSym3 k z a_6989586621679521933) a_6989586621679521933 

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_6989586621679521881 = Apply (Apply (Apply (Apply Lambda_6989586621679521886Sym0 f) g) a_6989586621679521881) a_6989586621679521881 

(%.) :: 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 (Let6989586621679521857VxSym2 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_6989586621679521831 = Apply (Let6989586621679521836GoSym3 p f a_6989586621679521831) a_6989586621679521831 

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_6989586621679521899 a_6989586621679521901 = Apply (Apply ConstSym0 a_6989586621679521899) a_6989586621679521901 

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 a6989586621679521718 b6989586621679521719. (~>) ((~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) ((~>) b6989586621679521719 ((~>) [a6989586621679521718] b6989586621679521719)) Source #

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (a6989586621679521718 ~> (b6989586621679521719 ~> b6989586621679521719)) (b6989586621679521719 ~> ([a6989586621679521718] ~> b6989586621679521719)) -> Type) (a6989586621679521927 :: a6989586621679521718 ~> (b6989586621679521719 ~> b6989586621679521719)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym0 :: TyFun (a6989586621679521718 ~> (b6989586621679521719 ~> b6989586621679521719)) (b6989586621679521719 ~> ([a6989586621679521718] ~> b6989586621679521719)) -> Type) (a6989586621679521927 :: a6989586621679521718 ~> (b6989586621679521719 ~> b6989586621679521719)) = FoldrSym1 a6989586621679521927

data FoldrSym1 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) :: (~>) b6989586621679521719 ((~>) [a6989586621679521718] b6989586621679521719) 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 a6989586621679521927 :: TyFun b6989586621679521719 ([a6989586621679521718] ~> b6989586621679521719) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 a6989586621679521927 :: TyFun b6989586621679521719 ([a6989586621679521718] ~> b6989586621679521719) -> Type) (a6989586621679521928 :: b6989586621679521719) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym1 a6989586621679521927 :: TyFun b6989586621679521719 ([a6989586621679521718] ~> b6989586621679521719) -> Type) (a6989586621679521928 :: b6989586621679521719) = FoldrSym2 a6989586621679521927 a6989586621679521928

data FoldrSym2 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) (a6989586621679521928 :: b6989586621679521719) :: (~>) [a6989586621679521718] b6989586621679521719 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 a6989586621679521928 a6989586621679521927 :: TyFun [a6989586621679521718] b6989586621679521719 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 a6989586621679521928 a6989586621679521927 :: TyFun [a] b -> Type) (a6989586621679521929 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FoldrSym2 a6989586621679521928 a6989586621679521927 :: TyFun [a] b -> Type) (a6989586621679521929 :: [a]) = Foldr a6989586621679521928 a6989586621679521927 a6989586621679521929

type FoldrSym3 (a6989586621679521927 :: (~>) a6989586621679521718 ((~>) b6989586621679521719 b6989586621679521719)) (a6989586621679521928 :: b6989586621679521719) (a6989586621679521929 :: [a6989586621679521718]) = Foldr a6989586621679521927 a6989586621679521928 a6989586621679521929 Source #

data MapSym0 :: forall a6989586621679521716 b6989586621679521717. (~>) ((~>) a6989586621679521716 b6989586621679521717) ((~>) [a6989586621679521716] [b6989586621679521717]) Source #

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679521716 ~> b6989586621679521717) ([a6989586621679521716] ~> [b6989586621679521717]) -> Type) (a6989586621679521920 :: a6989586621679521716 ~> b6989586621679521717) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (MapSym0 :: TyFun (a6989586621679521716 ~> b6989586621679521717) ([a6989586621679521716] ~> [b6989586621679521717]) -> Type) (a6989586621679521920 :: a6989586621679521716 ~> b6989586621679521717) = MapSym1 a6989586621679521920

data MapSym1 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) :: (~>) [a6989586621679521716] [b6989586621679521717] 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 a6989586621679521920 :: TyFun [a6989586621679521716] [b6989586621679521717] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type MapSym2 (a6989586621679521920 :: (~>) a6989586621679521716 b6989586621679521717) (a6989586621679521921 :: [a6989586621679521716]) = Map a6989586621679521920 a6989586621679521921 Source #

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

data (++@#@$$) (a6989586621679521912 :: [a6989586621679521715]) :: (~>) [a6989586621679521715] [a6989586621679521715] 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 ((++@#@$$) a6989586621679521912 :: TyFun [a6989586621679521715] [a6989586621679521715] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type (++@#@$$$) (a6989586621679521912 :: [a6989586621679521715]) (a6989586621679521913 :: [a6989586621679521715]) = (++) a6989586621679521912 a6989586621679521913 Source #

data IdSym0 :: forall a6989586621679521714. (~>) a6989586621679521714 a6989586621679521714 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 a6989586621679521714 a6989586621679521714 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type IdSym1 (a6989586621679521909 :: a6989586621679521714) = Id a6989586621679521909 Source #

data ConstSym0 :: forall a6989586621679521712 b6989586621679521713. (~>) a6989586621679521712 ((~>) b6989586621679521713 a6989586621679521712) Source #

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

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (ConstSym0 :: TyFun a6989586621679521712 (b6989586621679521713 ~> a6989586621679521712) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym0 :: TyFun a6989586621679521712 (b6989586621679521713 ~> a6989586621679521712) -> Type) (a6989586621679521894 :: a6989586621679521712) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym0 :: TyFun a6989586621679521712 (b6989586621679521713 ~> a6989586621679521712) -> Type) (a6989586621679521894 :: a6989586621679521712) = (ConstSym1 a6989586621679521894 b6989586621679521713 :: TyFun b6989586621679521713 a6989586621679521712 -> Type)

data ConstSym1 (a6989586621679521894 :: a6989586621679521712) :: forall b6989586621679521713. (~>) b6989586621679521713 a6989586621679521712 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 a6989586621679521894 b6989586621679521713 :: TyFun b6989586621679521713 a6989586621679521712 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (ConstSym1 a6989586621679521894 b :: TyFun b a -> Type) (a6989586621679521895 :: b) = Const a6989586621679521894 a6989586621679521895

type ConstSym2 (a6989586621679521894 :: a6989586621679521712) (a6989586621679521895 :: b6989586621679521713) = Const a6989586621679521894 a6989586621679521895 Source #

data (.@#@$) :: forall a6989586621679521711 b6989586621679521709 c6989586621679521710. (~>) ((~>) b6989586621679521709 c6989586621679521710) ((~>) ((~>) a6989586621679521711 b6989586621679521709) ((~>) a6989586621679521711 c6989586621679521710)) infixr 9 Source #

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

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings ((.@#@$) :: TyFun (b6989586621679521709 ~> c6989586621679521710) ((a6989586621679521711 ~> b6989586621679521709) ~> (a6989586621679521711 ~> c6989586621679521710)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (b6989586621679521709 ~> c6989586621679521710) ((a6989586621679521711 ~> b6989586621679521709) ~> (a6989586621679521711 ~> c6989586621679521710)) -> Type) (a6989586621679521875 :: b6989586621679521709 ~> c6989586621679521710) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply ((.@#@$) :: TyFun (b6989586621679521709 ~> c6989586621679521710) ((a6989586621679521711 ~> b6989586621679521709) ~> (a6989586621679521711 ~> c6989586621679521710)) -> Type) (a6989586621679521875 :: b6989586621679521709 ~> c6989586621679521710) = (a6989586621679521875 .@#@$$ a6989586621679521711 :: TyFun (a6989586621679521711 ~> b6989586621679521709) (a6989586621679521711 ~> c6989586621679521710) -> Type)

data (.@#@$$) (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) :: forall a6989586621679521711. (~>) ((~>) a6989586621679521711 b6989586621679521709) ((~>) a6989586621679521711 c6989586621679521710) 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 (a6989586621679521875 .@#@$$ a6989586621679521711 :: TyFun (a6989586621679521711 ~> b6989586621679521709) (a6989586621679521711 ~> c6989586621679521710) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521875 .@#@$$ a6989586621679521711 :: TyFun (a6989586621679521711 ~> b6989586621679521709) (a6989586621679521711 ~> c6989586621679521710) -> Type) (a6989586621679521876 :: a6989586621679521711 ~> b6989586621679521709) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521875 .@#@$$ a6989586621679521711 :: TyFun (a6989586621679521711 ~> b6989586621679521709) (a6989586621679521711 ~> c6989586621679521710) -> Type) (a6989586621679521876 :: a6989586621679521711 ~> b6989586621679521709) = a6989586621679521875 .@#@$$$ a6989586621679521876

data (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) .@#@$$$ (a6989586621679521876 :: (~>) a6989586621679521711 b6989586621679521709) :: (~>) a6989586621679521711 c6989586621679521710 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 (a6989586621679521876 .@#@$$$ a6989586621679521875 :: TyFun a6989586621679521711 c6989586621679521710 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521876 .@#@$$$ a6989586621679521875 :: TyFun a c -> Type) (a6989586621679521877 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (a6989586621679521876 .@#@$$$ a6989586621679521875 :: TyFun a c -> Type) (a6989586621679521877 :: a) = (a6989586621679521876 :. a6989586621679521875) a6989586621679521877

type (.@#@$$$$) (a6989586621679521875 :: (~>) b6989586621679521709 c6989586621679521710) (a6989586621679521876 :: (~>) a6989586621679521711 b6989586621679521709) (a6989586621679521877 :: a6989586621679521711) = (:.) a6989586621679521875 a6989586621679521876 a6989586621679521877 Source #

data ($@#@$) :: forall a6989586621679521703 b6989586621679521704. (~>) ((~>) a6989586621679521703 b6989586621679521704) ((~>) a6989586621679521703 b6989586621679521704) infixr 0 Source #

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

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (($@#@$) :: TyFun (a6989586621679521703 ~> b6989586621679521704) (a6989586621679521703 ~> b6989586621679521704) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$) :: TyFun (a6989586621679521703 ~> b6989586621679521704) (a6989586621679521703 ~> b6989586621679521704) -> Type) (a6989586621679521860 :: a6989586621679521703 ~> b6989586621679521704) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$) :: TyFun (a6989586621679521703 ~> b6989586621679521704) (a6989586621679521703 ~> b6989586621679521704) -> Type) (a6989586621679521860 :: a6989586621679521703 ~> b6989586621679521704) = ($@#@$$) a6989586621679521860

data ($@#@$$) (a6989586621679521860 :: (~>) a6989586621679521703 b6989586621679521704) :: (~>) a6989586621679521703 b6989586621679521704 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 (($@#@$$) a6989586621679521860 :: TyFun a6989586621679521703 b6989586621679521704 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (($@#@$$) a6989586621679521860 :: TyFun a b -> Type) (a6989586621679521861 :: a) = a6989586621679521860 $ a6989586621679521861

type ($@#@$$$) (a6989586621679521860 :: (~>) a6989586621679521703 b6989586621679521704) (a6989586621679521861 :: a6989586621679521703) = ($) a6989586621679521860 a6989586621679521861 Source #

data ($!@#@$) :: forall a6989586621679521701 b6989586621679521702. (~>) ((~>) a6989586621679521701 b6989586621679521702) ((~>) a6989586621679521701 b6989586621679521702) infixr 0 Source #

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$) :: TyFun (a6989586621679521701 ~> b6989586621679521702) (a6989586621679521701 ~> b6989586621679521702) -> Type) (a6989586621679521851 :: a6989586621679521701 ~> b6989586621679521702) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (($!@#@$) :: TyFun (a6989586621679521701 ~> b6989586621679521702) (a6989586621679521701 ~> b6989586621679521702) -> Type) (a6989586621679521851 :: a6989586621679521701 ~> b6989586621679521702) = ($!@#@$$) a6989586621679521851

data ($!@#@$$) (a6989586621679521851 :: (~>) a6989586621679521701 b6989586621679521702) :: (~>) a6989586621679521701 b6989586621679521702 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 (($!@#@$$) a6989586621679521851 :: TyFun a6989586621679521701 b6989586621679521702 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

type ($!@#@$$$) (a6989586621679521851 :: (~>) a6989586621679521701 b6989586621679521702) (a6989586621679521852 :: a6989586621679521701) = ($!) a6989586621679521851 a6989586621679521852 Source #

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679521700 ~> Bool) ((a6989586621679521700 ~> a6989586621679521700) ~> (a6989586621679521700 ~> a6989586621679521700)) -> Type) (a6989586621679521825 :: a6989586621679521700 ~> Bool) = UntilSym1 a6989586621679521825

data UntilSym1 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) :: (~>) ((~>) a6989586621679521700 a6989586621679521700) ((~>) a6989586621679521700 a6989586621679521700) 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 a6989586621679521825 :: TyFun (a6989586621679521700 ~> a6989586621679521700) (a6989586621679521700 ~> a6989586621679521700) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym1 a6989586621679521825 :: TyFun (a6989586621679521700 ~> a6989586621679521700) (a6989586621679521700 ~> a6989586621679521700) -> Type) (a6989586621679521826 :: a6989586621679521700 ~> a6989586621679521700) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym1 a6989586621679521825 :: TyFun (a6989586621679521700 ~> a6989586621679521700) (a6989586621679521700 ~> a6989586621679521700) -> Type) (a6989586621679521826 :: a6989586621679521700 ~> a6989586621679521700) = UntilSym2 a6989586621679521825 a6989586621679521826

data UntilSym2 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) (a6989586621679521826 :: (~>) a6989586621679521700 a6989586621679521700) :: (~>) a6989586621679521700 a6989586621679521700 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 a6989586621679521826 a6989586621679521825 :: TyFun a6989586621679521700 a6989586621679521700 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym2 a6989586621679521826 a6989586621679521825 :: TyFun a a -> Type) (a6989586621679521827 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym2 a6989586621679521826 a6989586621679521825 :: TyFun a a -> Type) (a6989586621679521827 :: a) = Until a6989586621679521826 a6989586621679521825 a6989586621679521827

type UntilSym3 (a6989586621679521825 :: (~>) a6989586621679521700 Bool) (a6989586621679521826 :: (~>) a6989586621679521700 a6989586621679521700) (a6989586621679521827 :: a6989586621679521700) = Until a6989586621679521825 a6989586621679521826 a6989586621679521827 Source #

data FlipSym0 :: forall a6989586621679521706 b6989586621679521707 c6989586621679521708. (~>) ((~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) ((~>) b6989586621679521707 ((~>) a6989586621679521706 c6989586621679521708)) Source #

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

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (FlipSym0 :: TyFun (a6989586621679521706 ~> (b6989586621679521707 ~> c6989586621679521708)) (b6989586621679521707 ~> (a6989586621679521706 ~> c6989586621679521708)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym0 :: TyFun (a6989586621679521706 ~> (b6989586621679521707 ~> c6989586621679521708)) (b6989586621679521707 ~> (a6989586621679521706 ~> c6989586621679521708)) -> Type) (a6989586621679521866 :: a6989586621679521706 ~> (b6989586621679521707 ~> c6989586621679521708)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym0 :: TyFun (a6989586621679521706 ~> (b6989586621679521707 ~> c6989586621679521708)) (b6989586621679521707 ~> (a6989586621679521706 ~> c6989586621679521708)) -> Type) (a6989586621679521866 :: a6989586621679521706 ~> (b6989586621679521707 ~> c6989586621679521708)) = FlipSym1 a6989586621679521866

data FlipSym1 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) :: (~>) b6989586621679521707 ((~>) a6989586621679521706 c6989586621679521708) 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 a6989586621679521866 :: TyFun b6989586621679521707 (a6989586621679521706 ~> c6989586621679521708) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym1 a6989586621679521866 :: TyFun b6989586621679521707 (a6989586621679521706 ~> c6989586621679521708) -> Type) (a6989586621679521867 :: b6989586621679521707) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym1 a6989586621679521866 :: TyFun b6989586621679521707 (a6989586621679521706 ~> c6989586621679521708) -> Type) (a6989586621679521867 :: b6989586621679521707) = FlipSym2 a6989586621679521866 a6989586621679521867

data FlipSym2 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) (a6989586621679521867 :: b6989586621679521707) :: (~>) a6989586621679521706 c6989586621679521708 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 a6989586621679521867 a6989586621679521866 :: TyFun a6989586621679521706 c6989586621679521708 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym2 a6989586621679521867 a6989586621679521866 :: TyFun a c -> Type) (a6989586621679521868 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (FlipSym2 a6989586621679521867 a6989586621679521866 :: TyFun a c -> Type) (a6989586621679521868 :: a) = Flip a6989586621679521867 a6989586621679521866 a6989586621679521868

type FlipSym3 (a6989586621679521866 :: (~>) a6989586621679521706 ((~>) b6989586621679521707 c6989586621679521708)) (a6989586621679521867 :: b6989586621679521707) (a6989586621679521868 :: a6989586621679521706) = Flip a6989586621679521866 a6989586621679521867 a6989586621679521868 Source #

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

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

Defined in Data.Singletons.Prelude.Base

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

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym0 :: TyFun a6989586621679521705 (a6989586621679521705 ~> a6989586621679521705) -> Type) (a6989586621679521903 :: a6989586621679521705) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym0 :: TyFun a6989586621679521705 (a6989586621679521705 ~> a6989586621679521705) -> Type) (a6989586621679521903 :: a6989586621679521705) = AsTypeOfSym1 a6989586621679521903

data AsTypeOfSym1 (a6989586621679521903 :: a6989586621679521705) :: (~>) a6989586621679521705 a6989586621679521705 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 a6989586621679521903 :: TyFun a6989586621679521705 a6989586621679521705 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym1 a6989586621679521903 :: TyFun a a -> Type) (a6989586621679521904 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (AsTypeOfSym1 a6989586621679521903 :: TyFun a a -> Type) (a6989586621679521904 :: a) = AsTypeOf a6989586621679521903 a6989586621679521904

type AsTypeOfSym2 (a6989586621679521903 :: a6989586621679521705) (a6989586621679521904 :: a6989586621679521705) = AsTypeOf a6989586621679521903 a6989586621679521904 Source #

data SeqSym0 :: forall a6989586621679521698 b6989586621679521699. (~>) a6989586621679521698 ((~>) b6989586621679521699 b6989586621679521699) infixr 0 Source #

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

Defined in Data.Singletons.Prelude.Base

SuppressUnusedWarnings (SeqSym0 :: TyFun a6989586621679521698 (b6989586621679521699 ~> b6989586621679521699) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym0 :: TyFun a6989586621679521698 (b6989586621679521699 ~> b6989586621679521699) -> Type) (a6989586621679521820 :: a6989586621679521698) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym0 :: TyFun a6989586621679521698 (b6989586621679521699 ~> b6989586621679521699) -> Type) (a6989586621679521820 :: a6989586621679521698) = (SeqSym1 a6989586621679521820 b6989586621679521699 :: TyFun b6989586621679521699 b6989586621679521699 -> Type)

data SeqSym1 (a6989586621679521820 :: a6989586621679521698) :: forall b6989586621679521699. (~>) b6989586621679521699 b6989586621679521699 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 a6989586621679521820 b6989586621679521699 :: TyFun b6989586621679521699 b6989586621679521699 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym1 a6989586621679521820 b :: TyFun b b -> Type) (a6989586621679521821 :: b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (SeqSym1 a6989586621679521820 b :: TyFun b b -> Type) (a6989586621679521821 :: b) = Seq a6989586621679521820 a6989586621679521821

type SeqSym2 (a6989586621679521820 :: a6989586621679521698) (a6989586621679521821 :: b6989586621679521699) = Seq a6989586621679521820 a6989586621679521821 Source #