Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
DeFun.Function
Description
Synopsis
- type family Id x where ...
- data IdSym x
- id :: a x -> a (Id x)
- idSym :: Lam a a IdSym
- type family Const x y where ...
- data ConstSym x
- data ConstSym1 x y
- const :: a x -> b y -> a x
- constSym :: Lam2 a b a ConstSym
- constSym1 :: a x -> Lam b a (ConstSym1 x)
- type family Flip f b a where ...
- data FlipSym f
- data FlipSym1 f x
- data FlipSym2 f b a
- flip :: Lam2 a b c f -> b x -> a y -> c (Flip f x y)
- flipSym :: Lam (a :~> (b :~> c)) (b :~> (a :~> c)) FlipSym
- flipSym1 :: Lam2 a b c f -> Lam2 b a c (FlipSym1 f)
- flipSym2 :: Lam2 a b c f -> b x -> Lam a c (FlipSym2 f x)
- type family Comp f g x where ...
- data CompSym f
- data CompSym1 f g
- data CompSym2 f g x
- comp :: Lam b c f -> Lam a b g -> a x -> c (Comp f g x)
- compSym :: Lam (b :~> c) (Lam a b :~> Lam a c) CompSym
- compSym1 :: Lam b c f -> Lam (a :~> b) (a :~> c) (CompSym1 f)
- compSym2 :: Lam b c f -> Lam a b g -> Lam a c (CompSym2 f g)
- type family Ap f g x where ...
- data ApSym f
- data ApSym1 f g
- data ApSym2 f g x
- ap :: Lam2 a b c f -> Lam a b g -> a x -> c (Ap f g x)
- apSym :: Lam3 (a :~> (b :~> c)) (a :~> b) a c ApSym
- apSym1 :: Lam2 a b c f -> Lam2 (a :~> b) a c (ApSym1 f)
- apSym2 :: Lam2 a b c f -> Lam a b g -> Lam a c (ApSym2 f g)
- type family Join f x where ...
- data JoinSym f
- data JoinSym1 f x
- join :: Lam2 a a b f -> a x -> b (Join f x)
- joinSym :: Lam2 (a :~> (a :~> b)) a b JoinSym
- joinSym1 :: Lam2 a a b fun -> Lam a b (JoinSym1 fun)
Id, I
type family Id x where ... Source #
Identity function. Combinator I
in https://en.wikipedia.org/wiki/SKI_combinator_calculus.
Equations
Id x = x |
Const, K
type family Const x y where ... Source #
Constant function. Combinator K
in https://en.wikipedia.org/wiki/SKI_combinator_calculus and https://en.wikipedia.org/wiki/B,_C,_K,_W_system.
Equations
Const x y = x |
Flip, C
type family Flip f b a where ... Source #
Function flip. Combinator C
in https://en.wikipedia.org/wiki/B,_C,_K,_W_system.
Comp, B
type family Comp f g x where ... Source #
Function composition. Combinator B
in https://en.wikipedia.org/wiki/B,_C,_K,_W_system.
Ap, S
type family Ap f g x where ... Source #
Combinator S
in https://en.wikipedia.org/wiki/SKI_combinator_calculus.
Join, W
type family Join f x where ... Source #
Combinator W
in https://en.wikipedia.org/wiki/B,_C,_K,_W_system