| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Symantic.Lib.Function
Description
Symantic for '(->)'.
Synopsis
- class Sym_Function term where
- tyFun :: Source src => LenInj vs => Type src vs (->)
- a0 :: Source src => LenInj vs => KindInj (K a) => Type src (Proxy a ': vs) a
- b1 :: Source src => LenInj vs => KindInj (K b) => Type src (a ': (Proxy b ': vs)) b
- c2 :: Source src => LenInj vs => KindInj (K c) => Type src (a ': (b ': (Proxy c ': vs))) c
- teFunction_compose :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((b -> c) -> (a -> b) -> a -> c))
- teFunction_const :: TermDef (->) '[Proxy a, Proxy b] (() #> (a -> b -> a))
- teFunction_flip :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((a -> b -> c) -> b -> a -> c))
- teFunction_id :: TermDef (->) '[Proxy a] (() #> (a -> a))
- teFunction_apply :: TermDef (->) '[Proxy a, Proxy b] (() #> ((a -> b) -> a -> b))
Class Sym_Function
class Sym_Function term where Source #
Methods
comp :: term (b -> c) -> term (a -> b) -> term (a -> c) infixr 9 Source #
const :: term a -> term b -> term a Source #
flip :: term (a -> b -> c) -> term (b -> a -> c) Source #
id :: term a -> term a Source #
comp :: Sym_Function (UnT term) => Trans term => term (b -> c) -> term (a -> b) -> term (a -> c) infixr 9 Source #
const :: Sym_Function (UnT term) => Trans term => term a -> term b -> term a Source #
flip :: Sym_Function (UnT term) => Trans term => term (a -> b -> c) -> term (b -> a -> c) Source #
id :: Sym_Function (UnT term) => Trans term => term a -> term a Source #
Instances
| Sym_Function View Source # | |
| Sym_Function Eval Source # | |
| (Sym_Function term, Sym_Lambda term) => Sym_Function (BetaT term) Source # | |
| Defined in Language.Symantic.Lib.Function | |
| (Sym_Function r1, Sym_Function r2) => Sym_Function (Dup r1 r2) Source # | |
Types
Terms
teFunction_compose :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((b -> c) -> (a -> b) -> a -> c)) Source #
teFunction_flip :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((a -> b -> c) -> b -> a -> c)) Source #
Orphan instances
| Gram_Term_AtomsFor src ss g ((->) :: * -> * -> *) Source # | |
| Methods g_term_atomsFor :: [CF g (AST_Term src ss)] # | |
| (Source src, SymInj ss ((->) :: * -> * -> *)) => ModuleFor src ss ((->) :: * -> * -> *) Source # | |
| ClassInstancesFor ((->) :: * -> * -> *) Source # | |
| TypeInstancesFor ((->) :: * -> * -> *) Source # | |
| NameTyOf ((->) :: * -> * -> *) Source # | |