symantic-lib-0.0.4.20180831: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.List

Contents

Description

Symantic for '[]'.

Synopsis

Class Sym_List

class Sym_List term where Source #

Methods

list_empty :: term [a] Source #

list_cons :: term a -> term [a] -> term [a] infixr 5 Source #

list :: [term a] -> term [a] Source #

zipWith :: term (a -> b -> c) -> term [a] -> term [b] -> term [c] Source #

list_empty :: Sym_List (UnT term) => Trans term => term [a] Source #

list_cons :: Sym_List (UnT term) => Trans term => term a -> term [a] -> term [a] infixr 5 Source #

list :: Sym_List (UnT term) => Trans term => [term a] -> term [a] Source #

zipWith :: Sym_List (UnT term) => Trans term => term (a -> b -> c) -> term [a] -> term [b] -> term [c] Source #

Instances
Sym_List View Source # 
Instance details

Defined in Language.Symantic.Lib.List

Methods

list_empty :: View [a] Source #

list_cons :: View a -> View [a] -> View [a] Source #

list :: [View a] -> View [a] Source #

zipWith :: View (a -> b -> c) -> View [a] -> View [b] -> View [c] Source #

Sym_List Eval Source # 
Instance details

Defined in Language.Symantic.Lib.List

Methods

list_empty :: Eval [a] Source #

list_cons :: Eval a -> Eval [a] -> Eval [a] Source #

list :: [Eval a] -> Eval [a] Source #

zipWith :: Eval (a -> b -> c) -> Eval [a] -> Eval [b] -> Eval [c] Source #

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

Defined in Language.Symantic.Lib.List

Methods

list_empty :: BetaT term [a] Source #

list_cons :: BetaT term a -> BetaT term [a] -> BetaT term [a] Source #

list :: [BetaT term a] -> BetaT term [a] Source #

zipWith :: BetaT term (a -> b -> c) -> BetaT term [a] -> BetaT term [b] -> BetaT term [c] Source #

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

Defined in Language.Symantic.Lib.List

Methods

list_empty :: Dup r1 r2 [a] Source #

list_cons :: Dup r1 r2 a -> Dup r1 r2 [a] -> Dup r1 r2 [a] Source #

list :: [Dup r1 r2 a] -> Dup r1 r2 [a] Source #

zipWith :: Dup r1 r2 (a -> b -> c) -> Dup r1 r2 [a] -> Dup r1 r2 [b] -> Dup r1 r2 [c] Source #

Types

tyList :: Source src => LenInj vs => Type src vs a -> Type src vs [a] Source #

Terms

teList_empty :: Source src => SymInj ss [] => Term src ss ts '[Proxy a] (() #> [a]) Source #

teList_cons :: Source src => SymInj ss [] => Term src ss ts '[Proxy a] (() #> (a -> [a] -> [a])) Source #

teList_zipWith :: Source src => SymInj ss [] => Term src ss ts '[Proxy a, Proxy b, Proxy c] (() #> ((a -> b -> c) -> [a] -> [b] -> [c])) Source #

Orphan instances

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 #

FixityOf [] Source # 
Instance details

Methods

fixityOf :: proxy [] -> Maybe Fixity #

(Source src, SymInj ss []) => ModuleFor src ss [] Source # 
Instance details

Methods

moduleFor :: (PathMod, Module src ss) #

(Gram_App g, Gram_Rule g, Gram_Comment g, Gram_Term src ss g, SymInj ss []) => Gram_Term_AtomsFor src ss g [] Source # 
Instance details

Methods

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