singletons-base-3.0: A promoted and singled version of the base library
Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Function.Singletons

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

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_6989586621679274050 = Apply (Apply (Apply (Apply Lambda_6989586621679274062Sym0 f) g) a_6989586621679274050) a_6989586621679274050 

(%.) :: 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_6989586621679298289 a_6989586621679298291 = Apply (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679298306Sym0 ty) f) a_6989586621679298289) a_6989586621679298291) a_6989586621679298289) a_6989586621679298291 

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 :: (~>) a a Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing IdSym0 #

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

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

type family IdSym1 (a6989586621679274074 :: a) :: a where ... Source #

Equations

IdSym1 a6989586621679274074 = Id a6989586621679274074 

data ConstSym0 :: (~>) a ((~>) b a) Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing ConstSym0 #

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

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679274069 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679274069 :: a) = ConstSym1 a6989586621679274069 :: TyFun b a -> Type

data ConstSym1 (a6989586621679274069 :: a) :: (~>) b a Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym1 d) #

SuppressUnusedWarnings (ConstSym1 a6989586621679274069 :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679274069 :: TyFun b a -> Type) (a6989586621679274070 :: b) = Const a6989586621679274069 a6989586621679274070

type family ConstSym2 (a6989586621679274069 :: a) (a6989586621679274070 :: b) :: a where ... Source #

Equations

ConstSym2 a6989586621679274069 a6989586621679274070 = Const a6989586621679274069 a6989586621679274070 

data (.@#@$) :: (~>) ((~>) b c) ((~>) ((~>) a b) ((~>) a c)) infixr 9 Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing (.@#@$) #

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

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679274056 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679274056 :: b ~> c) = (.@#@$$) a6989586621679274056 :: TyFun (a ~> b) (a ~> c) -> Type

data (.@#@$$) (a6989586621679274056 :: (~>) b c) :: (~>) ((~>) a b) ((~>) a c) infixr 9 Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

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

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

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679274056 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679274057 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679274056 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679274057 :: a ~> b) = a6989586621679274056 .@#@$$$ a6989586621679274057

data (a6989586621679274056 :: (~>) b c) .@#@$$$ (a6989586621679274057 :: (~>) a b) :: (~>) a c infixr 9 Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

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

SuppressUnusedWarnings (a6989586621679274056 .@#@$$$ a6989586621679274057 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679274056 .@#@$$$ a6989586621679274057 :: TyFun a c -> Type) (a6989586621679274058 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679274056 .@#@$$$ a6989586621679274057 :: TyFun a c -> Type) (a6989586621679274058 :: a) = (a6989586621679274056 . a6989586621679274057) a6989586621679274058

type family ((a6989586621679274056 :: (~>) b c) .@#@$$$$ (a6989586621679274057 :: (~>) a b)) (a6989586621679274058 :: a) :: c where ... infixr 9 Source #

Equations

(a6989586621679274056 .@#@$$$$ a6989586621679274057) a6989586621679274058 = (.) a6989586621679274056 a6989586621679274057 a6989586621679274058 

data FlipSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) b ((~>) a c)) Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing FlipSym0 #

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

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679274044 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679274044 :: a ~> (b ~> c)) = FlipSym1 a6989586621679274044

data FlipSym1 (a6989586621679274044 :: (~>) a ((~>) b c)) :: (~>) b ((~>) a c) Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym1 d) #

SuppressUnusedWarnings (FlipSym1 a6989586621679274044 :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679274044 :: TyFun b (a ~> c) -> Type) (a6989586621679274045 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679274044 :: TyFun b (a ~> c) -> Type) (a6989586621679274045 :: b) = FlipSym2 a6989586621679274044 a6989586621679274045

data FlipSym2 (a6989586621679274044 :: (~>) a ((~>) b c)) (a6989586621679274045 :: b) :: (~>) a c Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym2 d1 d2) #

SuppressUnusedWarnings (FlipSym2 a6989586621679274044 a6989586621679274045 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679274044 a6989586621679274045 :: TyFun a c -> Type) (a6989586621679274046 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679274044 a6989586621679274045 :: TyFun a c -> Type) (a6989586621679274046 :: a) = Flip a6989586621679274044 a6989586621679274045 a6989586621679274046

type family FlipSym3 (a6989586621679274044 :: (~>) a ((~>) b c)) (a6989586621679274045 :: b) (a6989586621679274046 :: a) :: c where ... Source #

Equations

FlipSym3 a6989586621679274044 a6989586621679274045 a6989586621679274046 = Flip a6989586621679274044 a6989586621679274045 a6989586621679274046 

data ($@#@$) :: (~>) ((~>) a b) ((~>) a b) infixr 0 Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

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

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

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

data ($@#@$$) (a6989586621679274025 :: (~>) a b) :: (~>) a b infixr 0 Source #

Instances

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

Defined in GHC.Base.Singletons

Methods

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

SuppressUnusedWarnings (($@#@$$) a6989586621679274025 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679274025 :: TyFun a b -> Type) (a6989586621679274026 :: a) = a6989586621679274025 $ a6989586621679274026

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

Equations

a6989586621679274025 $@#@$$$ a6989586621679274026 = ($) a6989586621679274025 a6989586621679274026 

data (&@#@$) :: (~>) a ((~>) ((~>) a b) b) infixl 1 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

sing :: Sing (&@#@$) #

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

Defined in Data.Function.Singletons

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

Defined in Data.Function.Singletons

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

data (&@#@$$) (a6989586621679298285 :: a) :: (~>) ((~>) a b) b infixl 1 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

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

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

Defined in Data.Function.Singletons

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

Defined in Data.Function.Singletons

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

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

Equations

a6989586621679298285 &@#@$$$ a6989586621679298286 = (&) a6989586621679298285 a6989586621679298286 

data OnSym0 :: (~>) ((~>) b ((~>) b c)) ((~>) ((~>) a b) ((~>) a ((~>) a c))) infixl 0 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

sing :: Sing OnSym0 #

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

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679298298 :: b ~> (b ~> c)) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679298298 :: b ~> (b ~> c)) = OnSym1 a6989586621679298298 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type

data OnSym1 (a6989586621679298298 :: (~>) b ((~>) b c)) :: (~>) ((~>) a b) ((~>) a ((~>) a c)) infixl 0 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym1 d) #

SuppressUnusedWarnings (OnSym1 a6989586621679298298 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679298298 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679298299 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679298298 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679298299 :: a ~> b) = OnSym2 a6989586621679298298 a6989586621679298299

data OnSym2 (a6989586621679298298 :: (~>) b ((~>) b c)) (a6989586621679298299 :: (~>) a b) :: (~>) a ((~>) a c) infixl 0 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym2 d1 d2) #

SuppressUnusedWarnings (OnSym2 a6989586621679298298 a6989586621679298299 :: TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679298298 a6989586621679298299 :: TyFun a (a ~> c) -> Type) (a6989586621679298300 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679298298 a6989586621679298299 :: TyFun a (a ~> c) -> Type) (a6989586621679298300 :: a) = OnSym3 a6989586621679298298 a6989586621679298299 a6989586621679298300

data OnSym3 (a6989586621679298298 :: (~>) b ((~>) b c)) (a6989586621679298299 :: (~>) a b) (a6989586621679298300 :: a) :: (~>) a c infixl 0 Source #

Instances

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

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym3 d1 d2 d3) #

SuppressUnusedWarnings (OnSym3 a6989586621679298298 a6989586621679298299 a6989586621679298300 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym3 a6989586621679298298 a6989586621679298299 a6989586621679298300 :: TyFun a c -> Type) (a6989586621679298301 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym3 a6989586621679298298 a6989586621679298299 a6989586621679298300 :: TyFun a c -> Type) (a6989586621679298301 :: a) = On a6989586621679298298 a6989586621679298299 a6989586621679298300 a6989586621679298301

type family OnSym4 (a6989586621679298298 :: (~>) b ((~>) b c)) (a6989586621679298299 :: (~>) a b) (a6989586621679298300 :: a) (a6989586621679298301 :: a) :: c where ... infixl 0 Source #

Equations

OnSym4 a6989586621679298298 a6989586621679298299 a6989586621679298300 a6989586621679298301 = On a6989586621679298298 a6989586621679298299 a6989586621679298300 a6989586621679298301