yall-0.2.1: Lenses with a southern twang

Safe HaskellNone

Data.Yall.Iso

Contents

Synopsis

Documentation

Iso is similar but more flexible than Lens in that they have no dependency on context. This flexibility affords a number of nice class instances that we don't get with Lens, so these can be quite useful in combination. See isoL for converting to Lens.

A less imprecise name for the code here might be Bijection but no one wants to type that.

data Iso w m a b Source

An Isomorphism or one-to-one mapping between types. These are very similar to a Lens, but are not dependent on context, making them more flexible. The functions also alow a Monadic context, supporting partial isomorphisms, and other interesting functionality.

Constructors

Iso 

Fields

apply :: a -> m b
 
unapply :: b -> w a
 

Instances

Monad m => Functor m (Iso m m) (Iso Identity Identity) 
(Monad m, Monad w) => PFunctor Either (Iso w m) (Iso w m) 
(Monad m, Monad w) => PFunctor (,) (Iso w m) (Iso w m) 
(Monad m, Monad w) => QFunctor Either (Iso w m) (Iso w m) 
(Monad m, Monad w) => QFunctor (,) (Iso w m) (Iso w m) 
(Monad m, Monad w) => Bifunctor Either (Iso w m) (Iso w m) (Iso w m) 
(Monad m, Monad w) => Bifunctor (,) (Iso w m) (Iso w m) (Iso w m) 
(Monad m, Monad w) => Category (Iso w m) 
(Monad m, Monad w) => Braided (Iso w m) Either 
(Monad m, Monad w) => Braided (Iso w m) (,) 
(Monad m, Monad w) => Symmetric (Iso w m) Either 
(Monad m, Monad w) => Symmetric (Iso w m) (,) 
(Monad m, Monad w) => Monoidal (Iso w m) (,) 
(Monad m, Monad w) => Associative (Iso w m) Either 
(Monad m, Monad w) => Associative (Iso w m) (,) 

inverseI :: (Monad m, Monad w) => Iso w m a b -> Iso m w b aSource

See also an Iso wrapped in Dual

Convenient Iso types

Pure isomorphisms

type :<-> a b = Iso Identity Identity a bSource

pure Iso

iso :: (Monad m, Monad w) => (a -> b) -> (b -> a) -> Iso w m a bSource

($-) :: (a :<-> b) -> a -> bSource

apply the forward function

 i $- a = runIdentity $ apply i a

(-$) :: (a :<-> b) -> b -> aSource

apply the backward function

 i -$ b = runIdentity $ unapply i b

Wrapped pure Iso

ifmap :: (Monad w, Monad m, Functor f IsoPure IsoPure) => Iso Identity Identity a b -> Iso w m (f a) (f b)Source

A more categorical fmap, with wrapping / unwrapping for convenience. See also the Functor instances for Iso.

 ifmap = fromPure . C.fmap . IsoPure

fromPure :: (Monad w, Monad m) => IsoPure a b -> Iso w m a bSource

Unwrap and make polymorphic an IsoPure

Pre-defined isomorphisms

Note: while all of these are pure and could be expressed as '(:-)', we define them polymorphically in Monad for maximum flexibility in composing with other Lens or Iso.

Also note that for most of these apply i . unapply i is not strictly id for the entire input domain, e.g. zipI obviously truncates lists of differing length, etc.

showI :: (Read s, Show s, Monad w, Monad m) => Iso w m s StringSource

curryI :: (Monad m, Monad w) => Iso w m ((a, b) -> c) (a -> b -> c)Source

enumI :: (Enum a, Monad m, Monad w) => Iso w m Int aSource

zipI :: (Monad m, Monad w) => Iso w m ([a], [b]) [(a, b)]Source

incrementI :: (Monad m, Monad w, Num a) => Iso w m a aSource

incrementByI :: (Monad m, Monad w, Num a) => a -> Iso w m a aSource

consI :: (Monad m, Monad w) => Iso w m (a, [a]) [a]Source

Calls fail on the empty list.

distributeI :: (Monad m, Monad w) => Iso w m (a, Either b c) (Either (a, b) (a, c))Source

factorI :: (Monad m, Monad w) => Iso w m (Either (a, b) (a, c)) (a, Either b c)Source

Partial isomorphisms

type :<~> a b = Iso Maybe Maybe a bSource

a partial Isomorphism