symantic-lib-0.0.4.20180831: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.Function

Contents

Description

Symantic for '(->)'.

Synopsis

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 # 
Instance details

Defined in Language.Symantic.Lib.Function

Methods

comp :: View (b -> c) -> View (a -> b) -> View (a -> c) Source #

const :: View a -> View b -> View a Source #

flip :: View (a -> b -> c) -> View (b -> a -> c) Source #

id :: View a -> View a Source #

Sym_Function Eval Source # 
Instance details

Defined in Language.Symantic.Lib.Function

Methods

comp :: Eval (b -> c) -> Eval (a -> b) -> Eval (a -> c) Source #

const :: Eval a -> Eval b -> Eval a Source #

flip :: Eval (a -> b -> c) -> Eval (b -> a -> c) Source #

id :: Eval a -> Eval a Source #

(Sym_Function term, Sym_Lambda term) => Sym_Function (BetaT term) Source # 
Instance details

Defined in Language.Symantic.Lib.Function

Methods

comp :: BetaT term (b -> c) -> BetaT term (a -> b) -> BetaT term (a -> c) Source #

const :: BetaT term a -> BetaT term b -> BetaT term a Source #

flip :: BetaT term (a -> b -> c) -> BetaT term (b -> a -> c) Source #

id :: BetaT term a -> BetaT term a Source #

(Sym_Function r1, Sym_Function r2) => Sym_Function (Dup r1 r2) Source # 
Instance details

Defined in Language.Symantic.Lib.Function

Methods

comp :: Dup r1 r2 (b -> c) -> Dup r1 r2 (a -> b) -> Dup r1 r2 (a -> c) Source #

const :: Dup r1 r2 a -> Dup r1 r2 b -> Dup r1 r2 a Source #

flip :: Dup r1 r2 (a -> b -> c) -> Dup r1 r2 (b -> a -> c) Source #

id :: Dup r1 r2 a -> Dup r1 r2 a Source #

Types

tyFun :: Source src => LenInj vs => Type src vs (->) Source #

a0 :: Source src => LenInj vs => KindInj (K a) => Type src (Proxy a ': vs) a Source #

b1 :: Source src => LenInj vs => KindInj (K b) => Type src (a ': (Proxy b ': vs)) b Source #

c2 :: Source src => LenInj vs => KindInj (K c) => Type src (a ': (b ': (Proxy c ': vs))) c Source #

Terms

teFunction_compose :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((b -> c) -> (a -> b) -> a -> c)) Source #

teFunction_const :: TermDef (->) '[Proxy a, Proxy b] (() #> (a -> b -> a)) Source #

teFunction_flip :: TermDef (->) '[Proxy a, Proxy b, Proxy c] (() #> ((a -> b -> c) -> b -> a -> c)) Source #

teFunction_id :: TermDef (->) '[Proxy a] (() #> (a -> a)) Source #

teFunction_apply :: TermDef (->) '[Proxy a, Proxy b] (() #> ((a -> b) -> a -> b)) Source #

Orphan instances

Gram_Term_AtomsFor src ss g ((->) :: * -> * -> *) Source # 
Instance details

Methods

g_term_atomsFor :: [CF g (AST_Term src ss)] #

(Source src, SymInj ss ((->) :: * -> * -> *)) => ModuleFor src ss ((->) :: * -> * -> *) Source # 
Instance details

Methods

moduleFor :: (PathMod, Module src ss) #

ClassInstancesFor ((->) :: * -> * -> *) Source # 
Instance details

Methods

proveConstraintFor :: Source src => proxy (->) -> Type src vs q -> Maybe (Qual q) #

TypeInstancesFor ((->) :: * -> * -> *) Source # 
Instance details

Methods

expandFamFor :: Source src => proxy (->) -> Len vs -> Const src fam -> Types src vs ts -> Maybe (Type src vs (Fam fam ts)) #

NameTyOf ((->) :: * -> * -> *) Source # 
Instance details

Methods

nameTyOf :: proxy (->) -> Mod NameTy #

isNameTyOp :: proxy (->) -> Bool #