singletons-2.5: A framework for generating singleton types

Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Function

Contents

Description

Defines singleton versions of the definitions in Data.Function.

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

Synopsis
  • 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 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 (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)
  • type family (a :: a) & (a :: (~>) a b) :: b where ...
  • (%&) :: forall a b (t :: a) (t :: (~>) a b). Sing t -> Sing t -> Sing (Apply (Apply (&@#@$) t) t :: b)
  • type family On (a :: (~>) b ((~>) b c)) (a :: (~>) a b) (a :: a) (a :: a) :: c where ...
  • sOn :: forall b c a (t :: (~>) b ((~>) b c)) (t :: (~>) a b) (t :: a) (t :: a). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply OnSym0 t) t) t) t :: c)
  • 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 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 ($@#@$) :: forall a6989586621679520914 b6989586621679520915. (~>) ((~>) a6989586621679520914 b6989586621679520915) ((~>) a6989586621679520914 b6989586621679520915)
  • data ($@#@$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) :: (~>) a6989586621679520914 b6989586621679520915
  • type ($@#@$$$) (a6989586621679521071 :: (~>) a6989586621679520914 b6989586621679520915) (a6989586621679521072 :: a6989586621679520914) = ($) a6989586621679521071 a6989586621679521072
  • data (&@#@$) :: forall a6989586621679729423 b6989586621679729424. (~>) a6989586621679729423 ((~>) ((~>) a6989586621679729423 b6989586621679729424) b6989586621679729424)
  • data (&@#@$$) (a6989586621679729436 :: a6989586621679729423) :: forall b6989586621679729424. (~>) ((~>) a6989586621679729423 b6989586621679729424) b6989586621679729424
  • type (&@#@$$$) (a6989586621679729436 :: a6989586621679729423) (a6989586621679729437 :: (~>) a6989586621679729423 b6989586621679729424) = (&) a6989586621679729436 a6989586621679729437
  • data OnSym0 :: forall a6989586621679729427 b6989586621679729425 c6989586621679729426. (~>) ((~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) ((~>) ((~>) a6989586621679729427 b6989586621679729425) ((~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426)))
  • data OnSym1 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) :: forall a6989586621679729427. (~>) ((~>) a6989586621679729427 b6989586621679729425) ((~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426))
  • data OnSym2 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) :: (~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426)
  • data OnSym3 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) (a6989586621679729444 :: a6989586621679729427) :: (~>) a6989586621679729427 c6989586621679729426
  • type OnSym4 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) (a6989586621679729444 :: a6989586621679729427) (a6989586621679729445 :: a6989586621679729427) = On a6989586621679729442 a6989586621679729443 a6989586621679729444 a6989586621679729445

Prelude re-exports

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 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 (a :: (~>) a b) $ (a :: a) :: b where ... infixr 0 Source #

Equations

f $ x = Apply f x 

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

Other combinators

type family (a :: a) & (a :: (~>) a b) :: b where ... infixl 1 Source #

Equations

x & f = Apply f x 

(%&) :: forall a b (t :: a) (t :: (~>) a b). Sing t -> Sing t -> Sing (Apply (Apply (&@#@$) t) t :: b) infixl 1 Source #

type family On (a :: (~>) b ((~>) b c)) (a :: (~>) a b) (a :: a) (a :: a) :: c where ... infixl 0 Source #

Equations

On ty f a_6989586621679729450 a_6989586621679729452 = Apply (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679729458Sym0 ty) f) a_6989586621679729450) a_6989586621679729452) a_6989586621679729450) a_6989586621679729452 

sOn :: forall b c a (t :: (~>) b ((~>) b c)) (t :: (~>) a b) (t :: a) (t :: a). Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply OnSym0 t) t) t) t :: c) infixl 0 Source #

Defunctionalization symbols

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 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 ($@#@$) :: 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 a6989586621679729423 b6989586621679729424. (~>) a6989586621679729423 ((~>) ((~>) a6989586621679729423 b6989586621679729424) b6989586621679729424) infixl 1 Source #

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

Defined in Data.Singletons.Prelude.Function

SuppressUnusedWarnings ((&@#@$) :: TyFun a6989586621679729423 ((a6989586621679729423 ~> b6989586621679729424) ~> b6989586621679729424) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply ((&@#@$) :: TyFun a6989586621679729423 ((a6989586621679729423 ~> b6989586621679729424) ~> b6989586621679729424) -> Type) (a6989586621679729436 :: a6989586621679729423) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply ((&@#@$) :: TyFun a6989586621679729423 ((a6989586621679729423 ~> b6989586621679729424) ~> b6989586621679729424) -> Type) (a6989586621679729436 :: a6989586621679729423) = (a6989586621679729436 &@#@$$ b6989586621679729424 :: TyFun (a6989586621679729423 ~> b6989586621679729424) b6989586621679729424 -> Type)

data (&@#@$$) (a6989586621679729436 :: a6989586621679729423) :: forall b6989586621679729424. (~>) ((~>) a6989586621679729423 b6989586621679729424) b6989586621679729424 infixl 1 Source #

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

Defined in Data.Singletons.Prelude.Function

Methods

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

SuppressUnusedWarnings (a6989586621679729436 &@#@$$ b6989586621679729424 :: TyFun (a6989586621679729423 ~> b6989586621679729424) b6989586621679729424 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (a6989586621679729436 &@#@$$ b :: TyFun (a ~> b) b -> Type) (a6989586621679729437 :: a ~> b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (a6989586621679729436 &@#@$$ b :: TyFun (a ~> b) b -> Type) (a6989586621679729437 :: a ~> b) = a6989586621679729436 & a6989586621679729437

type (&@#@$$$) (a6989586621679729436 :: a6989586621679729423) (a6989586621679729437 :: (~>) a6989586621679729423 b6989586621679729424) = (&) a6989586621679729436 a6989586621679729437 Source #

data OnSym0 :: forall a6989586621679729427 b6989586621679729425 c6989586621679729426. (~>) ((~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) ((~>) ((~>) a6989586621679729427 b6989586621679729425) ((~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426))) infixl 0 Source #

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

Defined in Data.Singletons.Prelude.Function

Methods

sing :: Sing OnSym0 Source #

SuppressUnusedWarnings (OnSym0 :: TyFun (b6989586621679729425 ~> (b6989586621679729425 ~> c6989586621679729426)) ((a6989586621679729427 ~> b6989586621679729425) ~> (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym0 :: TyFun (b6989586621679729425 ~> (b6989586621679729425 ~> c6989586621679729426)) ((a6989586621679729427 ~> b6989586621679729425) ~> (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426))) -> Type) (a6989586621679729442 :: b6989586621679729425 ~> (b6989586621679729425 ~> c6989586621679729426)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym0 :: TyFun (b6989586621679729425 ~> (b6989586621679729425 ~> c6989586621679729426)) ((a6989586621679729427 ~> b6989586621679729425) ~> (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426))) -> Type) (a6989586621679729442 :: b6989586621679729425 ~> (b6989586621679729425 ~> c6989586621679729426)) = (OnSym1 a6989586621679729442 a6989586621679729427 :: TyFun (a6989586621679729427 ~> b6989586621679729425) (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426)) -> Type)

data OnSym1 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) :: forall a6989586621679729427. (~>) ((~>) a6989586621679729427 b6989586621679729425) ((~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426)) infixl 0 Source #

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

Defined in Data.Singletons.Prelude.Function

Methods

sing :: Sing (OnSym1 d a) Source #

SuppressUnusedWarnings (OnSym1 a6989586621679729442 a6989586621679729427 :: TyFun (a6989586621679729427 ~> b6989586621679729425) (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym1 a6989586621679729442 a6989586621679729427 :: TyFun (a6989586621679729427 ~> b6989586621679729425) (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426)) -> Type) (a6989586621679729443 :: a6989586621679729427 ~> b6989586621679729425) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym1 a6989586621679729442 a6989586621679729427 :: TyFun (a6989586621679729427 ~> b6989586621679729425) (a6989586621679729427 ~> (a6989586621679729427 ~> c6989586621679729426)) -> Type) (a6989586621679729443 :: a6989586621679729427 ~> b6989586621679729425) = OnSym2 a6989586621679729442 a6989586621679729443

data OnSym2 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) :: (~>) a6989586621679729427 ((~>) a6989586621679729427 c6989586621679729426) infixl 0 Source #

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

Defined in Data.Singletons.Prelude.Function

Methods

sing :: Sing (OnSym2 d1 d2) Source #

SuppressUnusedWarnings (OnSym2 a6989586621679729443 a6989586621679729442 :: TyFun a6989586621679729427 (a6989586621679729427 ~> c6989586621679729426) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym2 a6989586621679729443 a6989586621679729442 :: TyFun a6989586621679729427 (a6989586621679729427 ~> c6989586621679729426) -> Type) (a6989586621679729444 :: a6989586621679729427) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym2 a6989586621679729443 a6989586621679729442 :: TyFun a6989586621679729427 (a6989586621679729427 ~> c6989586621679729426) -> Type) (a6989586621679729444 :: a6989586621679729427) = OnSym3 a6989586621679729443 a6989586621679729442 a6989586621679729444

data OnSym3 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) (a6989586621679729444 :: a6989586621679729427) :: (~>) a6989586621679729427 c6989586621679729426 infixl 0 Source #

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

Defined in Data.Singletons.Prelude.Function

Methods

sing :: Sing (OnSym3 d1 d2 d3) Source #

SuppressUnusedWarnings (OnSym3 a6989586621679729444 a6989586621679729443 a6989586621679729442 :: TyFun a6989586621679729427 c6989586621679729426 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym3 a6989586621679729444 a6989586621679729443 a6989586621679729442 :: TyFun a c -> Type) (a6989586621679729445 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Function

type Apply (OnSym3 a6989586621679729444 a6989586621679729443 a6989586621679729442 :: TyFun a c -> Type) (a6989586621679729445 :: a) = On a6989586621679729444 a6989586621679729443 a6989586621679729442 a6989586621679729445

type OnSym4 (a6989586621679729442 :: (~>) b6989586621679729425 ((~>) b6989586621679729425 c6989586621679729426)) (a6989586621679729443 :: (~>) a6989586621679729427 b6989586621679729425) (a6989586621679729444 :: a6989586621679729427) (a6989586621679729445 :: a6989586621679729427) = On a6989586621679729442 a6989586621679729443 a6989586621679729444 a6989586621679729445 Source #