symantic-lib-0.0.3.20180213: Symantics for common types.

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Lib.Ratio

Contents

Description

Symantic for Ratio.

Synopsis

Class Sym_Ratio

class Sym_Ratio term where Source #

Methods

ratio :: Integral a => term a -> term a -> term (Ratio a) Source #

numerator :: term (Ratio a) -> term a Source #

denominator :: term (Ratio a) -> term a Source #

ratio :: Sym_Ratio (UnT term) => Trans term => Integral a => term a -> term a -> term (Ratio a) Source #

numerator :: Sym_Ratio (UnT term) => Trans term => term (Ratio a) -> term a Source #

denominator :: Sym_Ratio (UnT term) => Trans term => term (Ratio a) -> term a Source #

Instances

Sym_Ratio View Source # 

Methods

ratio :: Integral a => View a -> View a -> View (Ratio a) Source #

numerator :: View (Ratio a) -> View a Source #

denominator :: View (Ratio a) -> View a Source #

Sym_Ratio Eval Source # 

Methods

ratio :: Integral a => Eval a -> Eval a -> Eval (Ratio a) Source #

numerator :: Eval (Ratio a) -> Eval a Source #

denominator :: Eval (Ratio a) -> Eval a Source #

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

Methods

ratio :: Integral a => BetaT term a -> BetaT term a -> BetaT term (Ratio a) Source #

numerator :: BetaT term (Ratio a) -> BetaT term a Source #

denominator :: BetaT term (Ratio a) -> BetaT term a Source #

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

Methods

ratio :: Integral a => Dup r1 r2 a -> Dup r1 r2 a -> Dup r1 r2 (Ratio a) Source #

numerator :: Dup r1 r2 (Ratio a) -> Dup r1 r2 a Source #

denominator :: Dup r1 r2 (Ratio a) -> Dup r1 r2 a Source #

Types

tyRatio :: Source src => Type src vs a -> Type src vs (Ratio a) Source #

Terms

teRatio :: TermDef Ratio '[Proxy a] (Integral a #> (a -> a -> Ratio a)) Source #

Orphan instances

ClassInstancesFor (* -> *) Ratio Source # 

Methods

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

TypeInstancesFor (* -> *) Ratio 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 (* -> *) Ratio Source # 

Methods

nameTyOf :: proxy c -> Mod NameTy #

isNameTyOp :: proxy c -> Bool #

FixityOf (* -> *) Ratio Source # 

Methods

fixityOf :: proxy c -> Maybe Fixity #

(Source src, SymInj (* -> *) ss Ratio) => ModuleFor (* -> *) src ss Ratio Source # 

Methods

moduleFor :: (PathMod, Module ss Ratio) #

Gram_Term_AtomsFor (* -> *) src ss g Ratio Source # 

Methods

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