| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Symantic.Lib.Ord
Description
Symantic for Ord.
- class Sym_Eq term => Sym_Ordering term where
- tyOrdering :: Source src => LenInj vs => Type src vs Ordering
- teOrdering :: Source src => SymInj ss Ordering => Ordering -> Term src ss ts '[] (() #> Ordering)
- class Sym_Eq term => Sym_Ord term where
- tyOrd :: Source src => Type src vs a -> Type src vs (Ord a)
- teOrd_compare :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> Ordering))
- teOrd_le :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> Bool))
- teOrd_lt :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> Bool))
- teOrd_ge :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> Bool))
- teOrd_gt :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> Bool))
- teOrd_min :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> a))
- teOrd_max :: TermDef Ord '[Proxy a] (Ord a #> (a -> a -> a))
Class Sym_Ordering
class Sym_Eq term => Sym_Ordering term where Source #
Methods
ordering :: Ordering -> term Ordering Source #
ordering :: Sym_Ordering (UnT term) => Trans term => Ordering -> term Ordering Source #
Instances
| Sym_Ordering View Source # | |
| Sym_Ordering Eval Source # | |
| (Sym_Ordering term, Sym_Lambda term) => Sym_Ordering (BetaT term) Source # | |
| (Sym_Ordering r1, Sym_Ordering r2) => Sym_Ordering (Dup r1 r2) Source # | |
Types
Terms
teOrdering :: Source src => SymInj ss Ordering => Ordering -> Term src ss ts '[] (() #> Ordering) Source #
Class Sym_Ord
class Sym_Eq term => Sym_Ord term where Source #
Methods
compare :: Ord a => term a -> term a -> term Ordering Source #
(<) :: Ord a => term a -> term a -> term Bool infix 4 Source #
(<=) :: Ord a => term a -> term a -> term Bool infix 4 Source #
(>) :: Ord a => term a -> term a -> term Bool infix 4 Source #
(>=) :: Ord a => term a -> term a -> term Bool infix 4 Source #
max :: Ord a => term a -> term a -> term a Source #
min :: Ord a => term a -> term a -> term a Source #
compare :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term Ordering Source #
(<) :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term Bool infix 4 Source #
(<=) :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term Bool infix 4 Source #
(>) :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term Bool infix 4 Source #
(>=) :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term Bool infix 4 Source #
max :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term a Source #
min :: Sym_Ord (UnT term) => Trans term => Ord a => term a -> term a -> term a Source #
Types
Terms
Orphan instances
| ClassInstancesFor * Ordering Source # | |
| TypeInstancesFor * Ordering Source # | |
| NameTyOf * Ordering Source # | |
| (Source src, SymInj * ss Ordering) => ModuleFor * src ss Ordering Source # | |
| Gram_Term_AtomsFor * src ss g Ordering Source # | |
| ClassInstancesFor (* -> Constraint) Ord Source # | |
| TypeInstancesFor (* -> Constraint) Ord Source # | |
| NameTyOf (* -> Constraint) Ord Source # | |
| FixityOf (* -> Constraint) Ord Source # | |
| (Source src, SymInj (* -> Constraint) ss Ord) => ModuleFor (* -> Constraint) src ss Ord Source # | |
| Gram_Term_AtomsFor (* -> Constraint) src ss g Ord Source # | |