cifl-math-library-1.1.1.0: Math libraries
Safe HaskellTrustworthy
LanguageHaskell2010

Math.Tools.Isomorphism

Synopsis

Documentation

data a :==: b Source #

See http://twanvl.nl/blog/haskell/isomorphism-lenses I also saw somewhere (can't remember where) a blog post for an idea for combinator library using isomorphisms. This is some sort of implementation of that idea.

Constructors

Iso 

Fields

Instances

Instances details
BiArrow (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

(<->) :: (a -> b) -> (b -> a) -> a :==: b Source #

Isomorphic (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

iso :: (a :==: b) -> a :==: b Source #

Category (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

id :: forall (a :: k). a :==: a #

(.) :: forall (b :: k) (c :: k) (a :: k). (b :==: c) -> (a :==: b) -> a :==: c #

Groupoid (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

invertA :: forall (a :: k) (b :: k). (a :==: b) -> b :==: a Source #

Arrow arr => ArrowTransformation (:==:) (arr :: Type -> Type -> Type) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

mapA :: forall (a :: k) (b :: k). (a :==: b) -> arr a b Source #

FunctorArrow Endo (:==:) (:==:) Source # 
Instance details

Defined in Math.Graph.GraphMonoid

Methods

amap :: forall (c :: k) (d :: k). (c :==: d) -> Endo c :==: Endo d Source #

FunctorArrow Vector2 (:==:) (:==:) Source # 
Instance details

Defined in Math.Matrix.Vector2

Methods

amap :: forall (c :: k) (d :: k). (c :==: d) -> Vector2 c :==: Vector2 d Source #

FunctorArrow I (:==:) (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

amap :: forall (c :: k) (d :: k). (c :==: d) -> I c :==: I d Source #

Limiting Stream (a :==: a) Source # 
Instance details

Defined in Math.Number.Stream

Associated Types

data Closure Stream (a :==: a) Source #

data Closure Stream (a :==: a) Source # 
Instance details

Defined in Math.Number.Stream

appIso :: Applicative f => f (a :==: b) -> f a :==: f b Source #

type Iso a b = a :==: b Source #

type Automorphism a = a :==: a Source #

leftIdempotent :: (a :==: b) -> Endo a Source #

https://en.wikipedia.org/Galois_Connection Note that since we don't check the equations for isomorphisms, this function need not produce identity.

rightIdempotent :: (a :==: b) -> Endo b Source #

https://en.wikipedia.org/Galois_Connection Note that since we don't check the equations for isomorphisms, this function need not produce an identity.

visit_iso :: ComposableVisitor v => (v :==: a) -> v -> a Source #

adjoint_iso :: Adjunction f g => (f a -> b) :==: (a -> g b) Source #

class (BiArrow arr, Groupoid arr) => Isomorphic arr where Source #

Methods

iso :: arr a b -> a :==: b Source #

Instances

Instances details
Isomorphic (:==:) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

iso :: (a :==: b) -> a :==: b Source #

Isomorphic ParsingA Source # 
Instance details

Defined in Math.Tools.ParsingCombinators

Methods

iso :: ParsingA a b -> a :==: b Source #

class IsomorphicFunctor f where Source #

Associated Types

data IsoA f a b Source #

Methods

transformIso :: IsoA f a b -> f a :==: f b Source #

Instances

Instances details
IsomorphicFunctor Var Source # 
Instance details

Defined in Math.Number.NumericExpression

Associated Types

data IsoA Var a b Source #

Methods

transformIso :: IsoA Var a b -> Var a :==: Var b Source #

FunctorArrow v (->) (->) => IsomorphicFunctor (NumExpr v) Source # 
Instance details

Defined in Math.Number.NumericExpression

Associated Types

data IsoA (NumExpr v) a b Source #

Methods

transformIso :: IsoA (NumExpr v) a b -> NumExpr v a :==: NumExpr v b Source #

FunctorArrow v (->) (->) => IsomorphicFunctor (VectorSpaceExpr v) Source # 
Instance details

Defined in Math.Number.NumericExpression

Associated Types

data IsoA (VectorSpaceExpr v) a b Source #

appIsoF :: IsomorphicFunctor f => IsoA f a b -> f a -> f b Source #

toArrow :: BiArrow arr => (a :==: b) -> arr a b Source #

abstract :: Isomorphic arr => (a :==: b) :==: arr a b Source #

runIso :: (a :==: b) -> a -> b Source #

type FRepresentable f a = forall r. (a -> r) -> f r Source #

type FCorepresentable f a = forall r. (r -> a) -> f r Source #

(=<) :: (a :==: b) -> a -> b Source #

liftIso :: Isomorphic arr => ((a :==: b) -> c :==: d) -> arr a b -> arr c d Source #

runIsoInverse :: (a :==: b) -> b -> a Source #

embedIso :: Groupoid cat => cat a b -> cat b b -> cat a a Source #

invertIso :: (a :==: b) -> b :==: a Source #

equalIso :: Eq a => (a, a) :==: Either a (a, a) Source #

inIso :: Rec f :==: f (Rec f) Source #

mapIso :: Functor f => (a :==: b) -> f a :==: f b Source #

inverseImageIso :: CoFunctor p => (a :==: b) -> p b :==: p a Source #

bimapIso :: (Functor f, CoFunctor f) => (a :==: b) -> (a :==: c) -> f c :==: f b Source #

orderedMapIso :: (MonadFail m, Ord i, Ord a) => Map i a -> Map a i -> m (i :==: a) Source #

constraint: all elements of the map must be present in both maps.

curryIso :: ((a, b) -> c) :==: (a -> b -> c) Source #

pairingIso :: (Integer, Integer) :==: Integer Source #

Cantor pairing function. Algorithm for the inverse is from https://secure.wikimedia.org/wikipedia/en/wiki/Pairing_function

absIso :: (Num a, Eq a) => a :==: Either a a Source #

ratioIso :: Integral a => (a, a) :==: (Ratio a, a) Source #

injectIso :: (a :==: b) -> (a :==: Either a b, b :==: Either a b) Source #

type Bot = forall a. a Source #

initialIso :: (BiArrow arr, Arrow arr') => arr () (arr' Bot a) Source #

terminalIso :: (Isomorphic arr, Arrow arr') => arr () (arr' a ()) Source #

productIso :: (BiArrow arr, Isomorphic arr, ArrowApply arr') => arr (arr' c (a, b)) (arr' c a, arr' c b) Source #

coproductIso :: (BiArrow arr, Isomorphic arr, ArrowChoice arr', ArrowApply arr') => arr (arr' (Either a b) c) (arr' a c, arr' b c) Source #

exponentialIso :: ArrowApply arr' => arr' (a, b) c :==: arr' a (arr' b c) Source #

eitherIso :: Isomorphic arr => arr a c1 -> arr b c2 -> arr (Either c1 c2) c -> arr (Either a b) c Source #

notIso :: BiArrow arr => arr Bool Bool Source #

boolIso :: BiArrow arr => arr Bool (Either () ()) Source #

assocIso :: BiArrow arr => arr ((a, b), c) (a, (b, c)) Source #

tripleIso :: BiArrow arr => arr (a, b, c) ((a, b), c) Source #

quadIso :: BiArrow arr => arr (a, b, c, d) ((a, b), (c, d)) Source #

pentaIso :: BiArrow arr => arr (a, b, c, d, e) ((a, b), c, (d, e)) Source #

zipEither :: BiArrow arr => arr (Either x y, Either a b) (Either (x, a) (Either (x, b) (Either (y, a) (y, b)))) Source #

distIso :: BiArrow arr => arr (Either (a, b) (a, c)) (a, Either b c) Source #

assocEitherIso :: BiArrow arr => arr (Either a (Either b c)) (Either (Either a b) c) Source #

terminalSecondIso :: BiArrow arr => arr (a, ()) a Source #

terminalThirdIso :: BiArrow arr => arr (a, b, ()) (a, b) Source #

terminalFourthIso :: BiArrow arr => arr (a, b, c, ()) (a, b, c) Source #

swapIso :: BiArrow arr => arr (a, b) (b, a) Source #

swapEitherIso :: BiArrow arr => arr (Either a b) (Either b a) Source #

(<**>) :: (a :==: b) -> (c :==: d) -> (a, c) :==: (b, d) Source #

product3 :: (a :==: b) -> (c :==: d) -> (e :==: f) -> (a, c, e) :==: (b, d, f) Source #

first3 :: (a :==: a') -> (a, b, c) :==: (a', b, c) Source #

second3 :: (b :==: b') -> (a, b, c) :==: (a, b', c) Source #

third3 :: (c :==: c') -> (a, b, c) :==: (a, b, c') Source #

(<||>) :: Isomorphic arr => arr a b -> arr c d -> arr (Either a c) (Either b d) Source #

ifIso :: Isomorphic arr => arr a b -> arr a c -> arr (a, Bool) (Either b c) Source #

branch :: Isomorphic arr => arr a b -> arr a c -> arr b d -> arr c d -> arr (a, Bool) (d, Bool) Source #

returnIso :: BiArrow arr => a -> arr () a Source #

fixIso :: Isomorphic arr => arr a a -> arr () (a, a) Source #

foldrIso :: ((a, [a]) :==: b) -> (Bool :==: b) -> [a] :==: b Source #

appendIso :: BiArrow arr => arr ([a], [a]) ([a], Int) Source #

listIso :: BiArrow arr => arr [a] (Either (a, [a]) ()) Source #

foldListIso :: (a :==: b) -> (() :==: d) -> (Either (b, c) d :==: c) -> [a] :==: c Source #

mapListIso :: (a :==: b) -> [a] :==: [b] Source #

This instance of map for list doesn't need fmap:

maybeIso :: BiArrow arr => arr (Maybe a) (Either a ()) Source #

data IsomorphismA arr a b Source #

Constructors

IsoA 

Fields

Instances

Instances details
Category arr => Category (IsomorphismA arr :: k -> k -> Type) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

id :: forall (a :: k0). IsomorphismA arr a a #

(.) :: forall (b :: k0) (c :: k0) (a :: k0). IsomorphismA arr b c -> IsomorphismA arr a b -> IsomorphismA arr a c #

Category arr => Groupoid (IsomorphismA arr :: k -> k -> Type) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

invertA :: forall (a :: k0) (b :: k0). IsomorphismA arr a b -> IsomorphismA arr b a Source #

Arrow arr => BiArrow (IsomorphismA arr) Source # 
Instance details

Defined in Math.Tools.Isomorphism

Methods

(<->) :: (a -> b) -> (b -> a) -> IsomorphismA arr a b Source #