symantic-lib-0.0.3.20180213: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.Semigroup

Contents

Description

Symantic for Semigroup.

Synopsis

Class Sym_Semigroup

class Sym_Semigroup term where Source #

Methods

(<>) :: Semigroup a => term a -> term a -> term a Source #

stimes :: (Semigroup a, Integral b) => term b -> term a -> term a Source #

(<>) :: Sym_Semigroup (UnT term) => Trans term => Semigroup a => term a -> term a -> term a Source #

stimes :: Sym_Semigroup (UnT term) => Trans term => Semigroup a => Integral b => term b -> term a -> term a Source #

Instances

Sym_Semigroup View Source # 

Methods

(<>) :: Semigroup a => View a -> View a -> View a Source #

stimes :: (Semigroup a, Integral b) => View b -> View a -> View a Source #

Sym_Semigroup Eval Source # 

Methods

(<>) :: Semigroup a => Eval a -> Eval a -> Eval a Source #

stimes :: (Semigroup a, Integral b) => Eval b -> Eval a -> Eval a Source #

(Sym_Semigroup term, Sym_Lambda term) => Sym_Semigroup (BetaT term) Source # 

Methods

(<>) :: Semigroup a => BetaT term a -> BetaT term a -> BetaT term a Source #

stimes :: (Semigroup a, Integral b) => BetaT term b -> BetaT term a -> BetaT term a Source #

(Sym_Semigroup r1, Sym_Semigroup r2) => Sym_Semigroup (Dup r1 r2) Source # 

Methods

(<>) :: Semigroup a => Dup r1 r2 a -> Dup r1 r2 a -> Dup r1 r2 a Source #

stimes :: (Semigroup a, Integral b) => Dup r1 r2 b -> Dup r1 r2 a -> Dup r1 r2 a Source #

Types

tySemigroup :: Source src => Type src vs a -> Type src vs (Semigroup a) Source #

Terms

Orphan instances

ClassInstancesFor (* -> Constraint) Semigroup Source # 

Methods

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

TypeInstancesFor (* -> Constraint) Semigroup Source # 

Methods

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

NameTyOf (* -> Constraint) Semigroup Source # 

Methods

nameTyOf :: proxy c -> Mod NameTy #

isNameTyOp :: proxy c -> Bool #

FixityOf (* -> Constraint) Semigroup Source # 

Methods

fixityOf :: proxy c -> Maybe Fixity #

(Source src, SymInj (* -> Constraint) ss Semigroup) => ModuleFor (* -> Constraint) src ss Semigroup Source # 
Gram_Term_AtomsFor (* -> Constraint) src ss g Semigroup Source #