oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Data.Opposite

Contents

Description

predicate for the opposite.

Synopsis

Op

newtype Op x Source #

Predicate for the opposite of a type x.

Constructors

Op x 

Instances

Instances details
Transformable1 Op Dst Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

Methods

tau1 :: Struct Dst x -> Struct Dst (Op x) Source #

Transformable1 Op Mlt Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

tau1 :: Struct Mlt x -> Struct Mlt (Op x) Source #

Transformable1 Op Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

tau1 :: Struct Ort x -> Struct Ort (Op x) Source #

Sliced i c => Sliced i (Op c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

Methods

slicePoint :: i (Op c) -> Point (Op c) Source #

Transformable1 Op (Alg k) Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Methods

tau1 :: Struct (Alg k) x -> Struct (Alg k) (Op x) Source #

XStandardOrtSite 'From a => XStandardOrtSite 'To (Op a) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Read x => Read (Op x) Source # 
Instance details

Defined in OAlg.Data.Opposite

Show x => Show (Op x) Source # 
Instance details

Defined in OAlg.Data.Opposite

Methods

showsPrec :: Int -> Op x -> ShowS #

show :: Op x -> String #

showList :: [Op x] -> ShowS #

Eq x => Eq (Op x) Source # 
Instance details

Defined in OAlg.Data.Opposite

Methods

(==) :: Op x -> Op x -> Bool #

(/=) :: Op x -> Op x -> Bool #

Validable x => Validable (Op x) Source # 
Instance details

Defined in OAlg.Data.Validable

Methods

valid :: Op x -> Statement Source #

Entity x => Entity (Op x) Source # 
Instance details

Defined in OAlg.Entity.Definition

(Abelian a, FibredOriented a) => Abelian (Op a) Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

negate :: Op a -> Op a Source #

(-) :: Op a -> Op a -> Op a Source #

ztimes :: Z -> Op a -> Op a Source #

(Additive a, FibredOriented a) => Additive (Op a) Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

zero :: Root (Op a) -> Op a Source #

(+) :: Op a -> Op a -> Op a Source #

ntimes :: N -> Op a -> Op a Source #

Algebraic a => Algebraic (Op a) Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Distributive d => Distributive (Op d) Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

FibredOriented f => Fibred (Op f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Op f) Source #

Methods

root :: Op f -> Root (Op f) Source #

FibredOriented f => FibredOriented (Op f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Cayleyan c => Cayleyan (Op c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Commutative c => Commutative (Op c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Invertible c => Invertible (Op c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

tryToInvert :: Op c -> Solver (Op c) Source #

invert :: Op c -> Op c Source #

isInvertible :: Op c -> Bool Source #

zpower :: Op c -> Z -> Op c Source #

Multiplicative c => Multiplicative (Op c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

one :: Point (Op c) -> Op c Source #

(*) :: Op c -> Op c -> Op c Source #

npower :: Op c -> N -> Op c Source #

EntityPoint x => EntityPoint (Op x) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Oriented q => Oriented (Op q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Op q) Source #

Methods

orientation :: Op q -> Orientation (Point (Op q)) Source #

start :: Op q -> Point (Op q) Source #

end :: Op q -> Point (Op q) Source #

Total x => Total (Op x) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

(Vectorial v, FibredOriented v) => Vectorial (Op v) Source # 
Instance details

Defined in OAlg.Structure.Vectorial.Definition

Associated Types

type Scalar (Op v) Source #

Methods

(!) :: Scalar (Op v) -> Op v -> Op v Source #

type Root (Op f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Root (Op f) = Orientation (Point f)
type Point (Op q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Point (Op q) = Point q
type Scalar (Op v) Source # 
Instance details

Defined in OAlg.Structure.Vectorial.Definition

type Scalar (Op v) = Scalar v

fromOp :: Op x -> x Source #

from Op x.

fromOpOp :: Op (Op x) -> x Source #

from Op (Op x).

Op2

newtype Op2 h x y Source #

Predicat for the opposite of a two parametrized type h where the two parameters x and y are switched

Constructors

Op2 (h y x) 

Instances

Instances details
Category c => Category (Op2 c) Source # 
Instance details

Defined in OAlg.Category.Definition

Methods

cOne :: Struct (ObjectClass (Op2 c)) x -> Op2 c x x Source #

(.) :: Op2 c y z -> Op2 c x y -> Op2 c x z Source #

Cayleyan2 c => Cayleyan2 (Op2 c) Source # 
Instance details

Defined in OAlg.Category.Definition

Methods

invert2 :: Op2 c x y -> Op2 c y x Source #

EmbeddableMorphismTyp m => EmbeddableMorphismTyp (Op2 m) Source # 
Instance details

Defined in OAlg.Category.Definition

Morphism h => Morphism (Op2 h) Source # 
Instance details

Defined in OAlg.Category.Definition

Associated Types

type ObjectClass (Op2 h) Source #

Methods

homomorphous :: Op2 h x y -> Homomorphous (ObjectClass (Op2 h)) x y Source #

domain :: Op2 h x y -> Struct (ObjectClass (Op2 h)) x Source #

range :: Op2 h x y -> Struct (ObjectClass (Op2 h)) y Source #

Eq2 h => Eq2 (Op2 h) Source # 
Instance details

Defined in OAlg.Data.Opposite

Methods

eq2 :: Op2 h x y -> Op2 h x y -> Bool Source #

Show2 h => Show2 (Op2 h) Source # 
Instance details

Defined in OAlg.Data.Opposite

Methods

show2 :: Op2 h a b -> String Source #

Validable2 h => Validable2 (Op2 h) Source # 
Instance details

Defined in OAlg.Data.Validable

Methods

valid2 :: Op2 h x y -> Statement Source #

EmbeddableMorphism m t => EmbeddableMorphism (Op2 m) t Source # 
Instance details

Defined in OAlg.Category.Definition

type ObjectClass (Op2 h) Source # 
Instance details

Defined in OAlg.Category.Definition