minilens-1.0.0.1: A minimalistic lens library, providing only the simplest, most basic lens functionality.

Safe HaskellNone
LanguageHaskell2010

Data.Lens.Minimal

Contents

Description

The Lens type aims to provide a very simple improvement on Haskell's record syntax: the idea of composable record accessors called Lenses.

Lenses also bring one of the strengths (or weaknesses, depending on your point of view) of Object-Oriented programming to Haskell: the idea of making setter and getter functions to control access to elements in data structures. A Lens combines both getters and setters into a single composable data type which can be invoked using simple functions like fetch or alter, or using infix operators such as ~>, <~, and $=.

Note that it is necessary to always include the following import statements in order to make use of Minimal Lenses:

import Prelude hiding ((.), id)
import Control.Category

With Haskell record syntax you can fetch and alter a data type like so:

let previousValue = record1 dat in
    dat{ record1 = newValue1, record2 = newValue2 }

With Minimal Lenses, it is possible to achieve the same thing with the following expression:

let previousValue = dat ~> recordName in
    with dat [ record1 <~ newValue1, record2 <~ newValue2 ]

Minimal Lenses can be composed with the Category operators (.), (<<<) and (>>>) so something like this:

return $ dat{ record = (\dat' -> dat'{ subRecord = newValue }) (record dat) }

can be simplified to this:

return $ with dat [ record >>> subRecord <~ newValue ]

or equivalently with the dot operator, which is identical to (>>>) with the arguments flipped:

return $ with dat [ subRecord . record <~ newValue ]

Fetching values is done with (~>), which is a left-handed infix operator of precedence 9 so that you can compose Lenses for fetching. The above example with record and subRecord could be fetched like so:

return (dat~>record~>subRecord)  -- uses tilde-greater-than, not hyphen-greater-than.

This is reminiscient of popular languages like C/C++ in which you could write the above with a similar expression:

return (dat->record->subRecord);

Synopsis

The Lens operators

(~>) :: c -> PureLens c e -> e infixl 9

The expression:

someContainer ~> getElem

will use a lens called getElem to fetch an element from the data structure called someContainer.

It looks and behaves similar to the C/C++ programming language operator ->. It is left associative (precedence 9) so the expression a~>b~>c~>d is the same as ((a ~> b) ~> c) ~> d, which means you can use this operator to compose Lenses to retrieve elements at arbitrary depth.

This function requires a PureLens, but of course any Lens polymorphic over the monadic type m can be used, automatic type inference will choose to make use of Identity if the type is polymorphic.

(<~) :: Monad m => Lens m c e -> e -> c -> m c infixr 0

This is a function intended to be used with the with, withM, by, or byM function. It is used for constructing a simple updating Endofunctor (updating function) that simply stores the element e into a container c using pureUpdate. You would use this operator when building a list of updates to pass to the with function.

This operator is visually similar to the bind operator used in Haskell's "do" notation (<-). Visually, it looks like you are writing a value into a lens, like in a procedural programming language where the field you want to modify is on the left of the assignment operator, and the value you want to write is on the right.

with myData [fieldInData <~ 0]

($=) :: Monad m => Lens m c e -> (e -> e) -> c -> m c infixr 0

This is a function intended to be used with the with, by, or new functions. It is used for constructing a simple updating Endofunctor (updating function) that updates element e inside of a container c using pureAlter. You would use this operator when building a list of updates to pass to the with function.

This operator is superficially similar to updating operators in popular C/C++ family of programming languages. In this languages, to do an in-place alter on a variable "x", for example to increment an integer "x" by 5, you would write: myData->x += 5;

Likewise this operator does an "in-place alter." However you must provide a _non_monadic_ function on the right-hand side of this operator that will perform the alter:

with myData [x $= (+ 5)]

($$=) :: Monad m => Lens m c e -> (e -> m e) -> c -> m c infixr 0

Like ($=), but the updater function is monadic.

(<$~>) :: Functor f => PureLens c e -> f c -> f e infixr 4

The ~> operator uses a Lens to fetch an element from a container. Often times, it is useful to use the Lens alone using Haskell's infix operator section syntax:

getter :: Container -> Element
getter container = container~>lensToGetElem
-- This can be abreviated to:

getter :: Container -> Element
getter = (~> lensToGetElem)

It is often useful to use a getter that we see above with Functors ' fmap infix operator: (<$>). For example:

fmapper :: [Container] -> [Element]
fmapper list = (~> lensToGetElem) <$> list

This pattern is used so often that it warrants it's own operator. The <$~> operator uses ('Data.Lens.Minimal.~>)' applies a lens to the element of a Functor using <$>. So the above fmapper could be written as:

fmapper :: [Container] -> [Element]
fmapper list = listToGetElem <$~> list

which can be further abbreviated to:

fmapper :: [Container] -> [Element]
fmapper = (listToGetElem <$~>)

Used as an infix operator, @(<$~>) is right-associative with a precedence of 4, making it the same fixity and associativity as the <$> and <*> functions.

fetch' :: Monad m => Lens m c e -> c -> m e

Use a Lens to read an element e within a container c. This function is usually used in do notation:

func container1 container2 = do
    elem container1 `fetch` a 'Control.Category.>>' b >>> c >>> d;
    foo  container2 `fetch` bar 'Control.Category.>>' baz
    combineAndReturn elem foo

fetch :: PureLens c e -> c -> e

Similar to fetch', but performs the lookup purely, without Monadic side-effects. It is usually easier to use the infix operator version of this function: (~>).

alter' :: Monad m => Lens m c e -> (e -> m e) -> c -> m c

Uses a Lens to extract an element e from a container c, then applies the element to the given monadic updating function (e -> m e), then places the element e back into the container c.

alter :: PureLens c e -> (e -> e) -> c -> c

Similar to alter but requires a PureLens and performs an alter with a pure function. It is usually easier to use the infix operator version of this function: ($=).

lensGet :: (Monad m, MonadState c m) => Lens m c e -> m e

Defined as (\lens -> get >>= fetch lens). Although instead of this function, it is usually easier to simply write:

get >>= fetch lens

or if your lens can be used as a PureLens:

gets (~> lens)

lensModify :: (Monad m, MonadState c m) => Lens m c e -> (e -> m e) -> m e

lensPut :: (Monad m, MonadState c m) => Lens m c e -> e -> m e

Use a Lens that can access the state within a MonadState function to alter the state. The lensPut function is defined as:

(\lens elem -> get >>= alter lens elem >>= \e -> put e >> return e)

Defining a sequence of updates

with :: c -> [c -> Identity c] -> c

The with function is defined to replace the Haskell programming language's own record alter syntax:

record{ field1=val1, field2=val2, ... fieldN=valN }

The with function simulates this record updating semantics with a visually similar syntax:

with record [ field1<~val1, field2<~val2, ... , field2<~val3 ]

But unlike the Haskell's record syntax, record fields are Lenses, which are composable. So it allows you write a record updating function like so:

moveSoutheast :: Gameboard -> Gameboard
moveSoutheast gameboard = with gameboard
    [ player >>> position >>> northCoord $= subtract 1
    , player >>> position >>> eastCoord $= (+ 1)
    , player >>> isMyTurn <~ False
    ]

The elements of the list passed to with can be any updating function to change elements in a container c. The list elements are of type (c -> Identity c), which are usually constructed using Lens operators like (<~) or ($=). Therefore any updating function may be used, not only functions constructed from Lens operators.

In category theory jargon, with applies a sequence of Endofunctors (updating functions) to a container c. The Endofunctors are applied in the order they appear in the list from left-to-right, therefore the mconcatenation of the Dual of each Endofunctor in the list [c -> c] is applied to the container c.

with' :: Monad m => c -> [c -> m c] -> m c

Identical to the with function, but performs each alter within a Monad. If the Monad is IO, then each alter may result in side-effects.

by :: [c -> Identity c] -> c -> c

This is the with function with the parameters flipped. It is convenient when used with modify when you want to alter the state of a StateT monad using a Lens. So take the example given in the with section above, the function could be written as:

moveSoutheast :: Gameboard -> Gameboard
moveSoutheast = by
    [ player >>> position >>> northCoord $= subtract 1
    , player >>> position >>> eastCoord $= (+ 1)
    , player >>> isMyTurn <~ False
    ]

by' :: Monad m => [c -> m c] -> c -> m c

Monadic version of by.

The Lens data type

newtype Lens m c e

A Lens is a StateT monadic function that lifts a monad m, and can perform an alter on an element e stored within a container c.

The Lens newtype contains a pair of functions. The first function is the fetch function (which is evaluated when you call fetch on a Lens). The second function is the alter function (which is evaluated when you call alter on a Lens).

Although you will usually construct lenses using the newLens or newLens' functions, lets take a look at how Lenses work by constructing a Lens with the Lens constructur, taking a simple container data type as an example. The Container will be a pair elements, each element being of the same type: e. So here is how we would define our simplified version of the containerFirst lens:

data Container e = Container e e

containerFirst :: Monad m => Lens m (Container e) e
containerFirst = Lens (          (Container e0    e1) -> return e0
                      , updateE0 (Container oldE0 e1) -> do
                           newE0 <- updateE0 e0
                           return (Container newE0 c1)
                      )

But as stated above, it is usually easier to use newLens instead of the Lens constructor. The newLens function takes a new element, rather than an updating function.

containerFirst :: Monad m => Lens m (Container e) e
containerFirst = newLens (       (Container e0 e1) -> e0
                         , newE0 (Container _  e1) -> Container newE0 e1
                         )

There is one law that the fetching and altering functions must follow. These laws cannot be checked by the compiler, so it is the duty of you, the programmer using this module, to make sure your code obeys these laws:

The element must be fetched from the exact same place that the alter function alters, and the altering function must alter the element retrieved by the fetching function. Lets look at the above containerFirst example again, and change it to make it _illegal_:

containerFirst :: Monad m => Lens m (Container e) e
containerFirst = Lens (         \ (Container e0 e1) -> e0
                      , \updateE0 (Container e0 e1) -> do
                          newE0 <- updateE0 e0
                          return (Container e0 newE0) -- NO! This is illegal.
                      )

Notice that the fetch function retrieved the first element e0, but the altering function altered the second element e1 (it returned a Container with the updated e0 in the spot where e1 used to be), and did it not alter the old e0. This would cause some extraordinarily confusing problems, so never do this.

Constructors

Lens (c -> m e, (e -> m e) -> c -> m c) 

Instances

Monad m => Category * (Lens m) 

type PureLens c e = Lens Identity c e

This is a Lens where the monad must be Identity. The advantage of using this over Lens (apart from the fact that it is easier to write it's type in your code) is that it guarantees access to your container must be pure, with no IO.

newLens :: Monad m => (c -> e, e -> c -> c) -> Lens m c e

Construct a Lens (polymorphic over the monadic type) from a pair of functions: fst being a function that fetches an element e from a container c, and snd being a function that places an element e into the a container c.

newLens' :: Monad m => (c -> m e, e -> c -> m c) -> Lens m c e

Like newLens, but take monadic fetch and alter functions.

isoLens :: Monad m => Iso m c e -> Lens m c e

Like newLens but uses an Iso to construct the Lens. Often times a Lens simply operates on an element within some container. Converting between the contained and the contained element is an Isomorphic operation, so a lens operating on the contained element can easily be constructed from an Isomorphism.

It is sometimes covenient, when designing your API, to export an Isomorphism for your newtype, rather than a constructor. This allows programmers using you API to use make and un to wrap and unwrap the newtype, and to use this isoLens function to access elements within the newtype using the lens operators.

liftLens :: (Monad m, MonadTrans t, Monad (t m)) => Lens m c e -> Lens (t m) c e

Use lift to lift the operating monad of the Lens. This is useful when you want to modify the behavior of an existing Lens by changing the monad in which alter and fetch operate. One example of how this could be used is if you want alter or fetch to be able to throw an error message, you could lift the monad into an ExceptT monad.

data Container = Container (Maybe Int) (Maybe String)

maybeInt :: Monad m => Lens m Container (Maybe Int)
maybeInt = newLens (\ (Container i _) -> i, \i (Container _ s) -> Container i s)

maybeString :: Monad m => Lens m Container (Maybe String)
maybeString = newLens (\ (Container _ s) -> s, \s (Container i _) -> Container i s)

required :: Monad m => String -> Lens m Container (Maybe element) -> Lens (ExceptT String m) Container element
required fieldName lens = liftLens lens >>>
    defaul' True (throwError $ fieldName++" is undefined") return

requireInt :: Monad m => Lens (ExceptT String m) Container Int
requireInt = required "int" maybeInt

requireString :: Monad m => Lens (ExceptT String m) Container String
requireString = required "string" maybeString

Lens combinators

new :: Monoid c => [c -> Identity c] -> c

Like with but passes mempty as the first parameter, so instead of writing something like:

with mempty [foo <~ 0, bar <~ 1]

All you have to write is:

new [foo <~ 0, bar <~ 1]

new' :: (Monad m, Monoid c) => [c -> m c] -> m c

Monadic version of new

defaul' :: Monad m => m e -> Lens m (Maybe e) e

The defaul Lens operates on the element of a Maybe data type given a default value if the structure contains Nothing. The structure will not be updated if it is Nothing, so it will not alter a Map data structure unless the key being updated already exists. This function is not called default because default is a reserved word in Haskell.

Try this in GHCi:

with (Just 10) [defaul' (return 0) $= (+ 5)] 
-- evaluates to (Just 15)
with Nothing [defaul' (return 0) $= (+ 5)] 
-- evaluates to Nothing

defaul :: Monad m => e -> Lens m (Maybe e) e

This Lens is shorthand for (defaul' . return)

Try this in GHCi:

with (Just 10) [defaul 0 $= (+ 5)] 
-- evaluates to (Just 15)
with Nothing [defaul 0 $= (+ 5)] 
-- evaluates to Nothing

ifJust :: (Monad m, Monoid e) => Lens m (Maybe e) e

The ifJust lens only works if the element in the container is not Nothing. This Lens is shorthand for (defaul mempty). This Lens accesss the element or returns mempty. If a non-existent element is updated, nothing is changed -- changes only occur if the element is not Nothing.

Try this in GHCi:

import Data.Monoid
import Data.Functor
getSum <$> with (Just 10) [ifJust $= (+ 5)] 
-- evaluates to (Just 15)
getSum <$> with Nothing [ifJust $= (+ 5)] 
-- evaluates to Nothing

orElse' :: Monad m => m e -> Lens m (Maybe e) e

The orElse' Lens operates on the element of a Maybe data type given a default value if the structure contains Nothing. The structure will be changed to the updated default value if it is Nothing. So if this function is used to alter a Map data structure where no element is associated with a given key, this function will force the value to exist and be associated with the given key.

Try this in GHCi:

with (Just 10) [orElse' (return 0) $= (+ 5)] 
-- evaluates to (Just 15)
with Nothing [orElse' (return 0) $= (+ 5)] 
-- evaluates to (Just 5)

orElse :: Monad m => e -> Lens m (Maybe e) e

This Lens is shorthand for (orElse' . return).

Try this in GHCi:

with (Just 10) [orElse 0 $= (+ 5)] 
-- evaluates to (Just 15)
with Nothing [orElse 0 $= (+ 5)] 
-- evaluates to (Just 5)

just :: (Monad m, Monoid e) => Lens m (Maybe e) e

This function is shorthand for (orElse mempty). This Lens accesses the element, it forces the element to mempty if it does not exist.

Try this in GHCi:

import Data.Monoid
import Data.Functor
getSum <$> with (Just 10) [just $= (+ 5)] 
-- evaluates to (Just 15)
getSum <$> with Nothing [just $= (+ 5)] 
-- evaluates to (Just 5)

notEmpty :: Monad m => (sub -> Bool) -> sub -> Lens m (Maybe sub) sub

This lens looks at a sub-container type sub within a Maybe container. Pass a predicate that evaluates to True if the sub-container is empty, and an empty sub container. When fetch-ing using this lens, if the container is Nothing this lens evaluates to the given empty sub-container. When alter-ing, if the updated sub-container is empty according to the given predicate, the container becomes Nothing. For example, in GHCi:

with (Just [1, 2]) [notEmpty null [] $= fmap (+ 10)]
-- evaluates to [11, 12]

with (Just [1, 2]) [notEmpty null [] $= tail]
-- evaluates to [2]

with (Just [1, 2])
    [ notEmpty null [] $= tail -- removes the first element
    , notEmpty null [] $= tail -- removes the second (and final) element
       -- The list we started with is now empty.
    ]
-- evaluates to Nothing

with (Just [0..]) [notEmpty null [] <~ []] -- store a null list
-- evaluates to Nothing

with Nothing [notEmpty null [] $= (0 :)]
-- evaluates to [0]

notMEmpty :: (Monad m, Eq sub, Monoid sub) => Lens m (Maybe sub) sub

Like notEmpty but uses a Monoid that satisfies Eq-uality. This function is shorthand for

notEmpty (== mempty) mempty

exists :: MonadPlus m => Lens m (Maybe e) e

This is a non-pure Lens that requires the mondic type instantiate MonadPlus so it can function as a kind of guard function. This Lens operates on a Maybe data structure. The Lens will fetch or alter a value if and only if the data structure is Just. If it is Nothing the Lens will evaluate to mzero.

leftLens :: MonadPlus m => Lens m (Either e anything) e

This is a non-pure Lens that requires the monadic type instantiate MonadPlus. This Lens operates on a EIther data structure. The Lens will fetch or alter a value if and only if the data structure is Left, otherwise the Lens evaluates to mzero.

rightLens :: MonadPlus m => Lens m (Either anything e) e

This is a non-pure Lens that requires the monadic type instantiate MonadPlus. This Lens operates on a Either data structure. The Lens will fetch or alter a value if and only if the data structure is Left, otherwise the Lens evaluates to mzero.

Lenses for containers

mapLens :: (Monad m, Eq key, Ord key) => key -> Lens m (Map key o) (Maybe o)

A Lens that focuses on an element of an Map with the key to that element.

intMapLens :: Monad m => Int -> Lens m (IntMap o) (Maybe o)

A Lens that focuses on an element of an IntMap with the key to that element.

intMapListLens :: Monad m => Lens m (IntMap o) [(Key, o)]

mapListLens :: (Monad m, Ord key) => Lens m (Map key o) [(key, o)]

dictionaryLens :: (Monad m, Eq key, Ord key) => (key -> map o -> Maybe o) -> ((Maybe o -> Maybe o) -> key -> map o -> map o) -> key -> Lens m (map o) (Maybe o)

To create a Lens that focuses on an element of a dictionary, provide a lookup function (e.g. lookup) and an alter function (e.g. alter). Or just use the mapLens or intMapLens functions predefined for the Map and IntMap data types, respectively.

arrayLens :: (Monad m, Ix i, IArray arr o) => i -> Lens m (arr i o) o

Create a lens that accesses an element at the given index in an array -- without bounds checking, so this lens evaluates to undefined if the index is out of bounds.

maybeArrayLens :: (Monad m, Ix i, IArray arr o) => i -> Lens m (arr i o) (Maybe o)

Create a lens that accesses an element at the given index in an array with bounds checking. Evaluates

ioArrayLens :: (Monad m, MonadIO m, Ix i, MArray arr o IO) => i -> Lens m (arr i o) o

ioMaybeArrayLens :: (Monad m, MonadIO m, Ix i, MArray arr o IO) => i -> Lens m (arr i o) (Maybe o)

Checks if the index is within the bounds of the array, does no lookup or alter if the index is out of bounds.

ioRefLens :: (Monad m, MonadIO m) => Lens m (IORef o) o

mvarLens :: (Monad m, MonadIO m) => Lens m (MVar o) o

Lenses for tuples

This section provides 10 lenses: tuple0, tuple1, tuple2, tuple3, tuple4, tuple5, tuple6, tuple7, tuple8, and tuple9. The left-most element is the zero'th element. These functions are all type class methods, because every different size of tuple is a different type.

If you end up using tuples with more than 10 elements, consider this a "code smell," (a sign that you are working with a program of bad design), and try to break-up your tuples into smaller units, perhaps units wrapped in newtypes.

class TupleLens0 a o where

Methods

tuple0 :: Monad m => Lens m a o

Instances

TupleLens0 (o, b) o 
TupleLens0 (o, b, c) o 
TupleLens0 (o, b, c, d) o 
TupleLens0 (o, b, c, d, e) o 
TupleLens0 (o, b, c, d, e, f) o 
TupleLens0 (o, b, c, d, e, f, g) o 
TupleLens0 (o, b, c, d, e, f, g, h) o 
TupleLens0 (o, b, c, d, e, f, g, h, i) o 
TupleLens0 (o, b, c, d, e, f, g, h, i, j) o 

class TupleLens1 a o where

Methods

tuple1 :: Monad m => Lens m a o

Instances

TupleLens1 (a, o) o 
TupleLens1 (a, o, c) o 
TupleLens1 (a, o, c, d) o 
TupleLens1 (a, o, c, d, e) o 
TupleLens1 (a, o, c, d, e, f) o 
TupleLens1 (a, o, c, d, e, f, g) o 
TupleLens1 (a, o, c, d, e, f, g, h) o 
TupleLens1 (a, o, c, d, e, f, g, h, i) o 
TupleLens1 (a, o, c, d, e, f, g, h, i, j) o 

class TupleLens2 a o where

Methods

tuple2 :: Monad m => Lens m a o

Instances

TupleLens2 (a, b, o) o 
TupleLens2 (a, b, o, d) o 
TupleLens2 (a, b, o, d, e) o 
TupleLens2 (a, b, o, d, e, f) o 
TupleLens2 (a, b, o, d, e, f, g) o 
TupleLens2 (a, b, o, d, e, f, g, h) o 
TupleLens2 (a, b, o, d, e, f, g, h, i) o 
TupleLens2 (a, b, o, d, e, f, g, h, i, j) o 

class TupleLens3 a o where

Methods

tuple3 :: Monad m => Lens m a o

Instances

TupleLens3 (a, b, c, o) o 
TupleLens3 (a, b, c, o, e) o 
TupleLens3 (a, b, c, o, e, f) o 
TupleLens3 (a, b, c, o, e, f, g) o 
TupleLens3 (a, b, c, o, e, f, g, h) o 
TupleLens3 (a, b, c, o, e, f, g, h, i) o 
TupleLens3 (a, b, c, o, e, f, g, h, i, j) o 

class TupleLens4 a o where

Methods

tuple4 :: Monad m => Lens m a o

Instances

TupleLens4 (a, b, c, d, o) o 
TupleLens4 (a, b, c, d, o, f) o 
TupleLens4 (a, b, c, d, o, f, g) o 
TupleLens4 (a, b, c, d, o, f, g, h) o 
TupleLens4 (a, b, c, d, o, f, g, h, i) o 
TupleLens4 (a, b, c, d, o, f, g, h, i, j) o 

class TupleLens5 a o where

Methods

tuple5 :: Monad m => Lens m a o

Instances

TupleLens5 (a, b, c, d, e, o) o 
TupleLens5 (a, b, c, d, e, o, g) o 
TupleLens5 (a, b, c, d, e, o, g, h) o 
TupleLens5 (a, b, c, d, e, o, g, h, i) o 
TupleLens5 (a, b, c, d, e, o, g, h, i, j) o 

class TupleLens6 a o where

Methods

tuple6 :: Monad m => Lens m a o

Instances

TupleLens6 (a, b, c, d, e, f, o) o 
TupleLens6 (a, b, c, d, e, f, o, h) o 
TupleLens6 (a, b, c, d, e, f, o, h, i) o 
TupleLens6 (a, b, c, d, e, f, o, h, i, j) o 

class TupleLens7 a o where

Methods

tuple7 :: Monad m => Lens m a o

Instances

TupleLens7 (a, b, c, d, e, f, g, o) o 
TupleLens7 (a, b, c, d, e, f, g, o, i) o 
TupleLens7 (a, b, c, d, e, f, g, o, i, j) o 

class TupleLens8 a o where

Methods

tuple8 :: Monad m => Lens m a o

Instances

TupleLens8 (a, b, c, d, e, f, g, h, o) o 
TupleLens8 (a, b, c, d, e, f, g, h, o, j) o 

class TupleLens9 a o where

Methods

tuple9 :: Monad m => Lens m a o

Instances

TupleLens9 (a, b, c, d, e, f, g, h, i, o) o 

Isomorphisms

newtype Iso m whole parts

This is a simple isomorphism data type, it contains a function and it's inverse, and instantiates Category. An Iso-morphism is a relationship between a whole and it's parts: it makes the whole from parts, and can un-make the whole back into it's parts, without ever losing anything in the process.

When building your own Iso-morphisms, it is a law -- a law which cannot be enforced by the compiler, so it is you the programmer's duty to obey this law -- that the second function _must_ be an inverse of the first function, i.e. the following funtion must always return True:

example :: forall m whole parts . Monad m => Iso m whole parts -> whole -> m Bool
example iso whole0 = do
    parts  <- un'   iso whole0
    whole1 <- make' iso parts
    return (whole0 == whole1) -- *must* be True, by law

When creating an Iso-morphism for newtypes, the convetion established by this module is that the fst function in the pair is the function that unwraps/deconstructs the newtype, and the snd function is the function that wraps/constructs the newtype.

This is decided by how the un and make functions work. For example, when using the identity Iso-morphism, make identity is the same as using the Identity constructor because make uses the snd function to call the Identity constructor. Likewise calling un identity is the same runIdentity because un uses the fst function to call runIdentity.

It can be difficult to remember this type definition of Iso, and that the first polymophic parameter is whole, and the second polymorphic paramter is parts. So as a mnemonic keep in mind the phrase, "the whole is greater than the sum of the parts," the order the words appear in that phrase is the same as the order of polymorphic type parameters.

Constructors

Iso (Kleisli m whole parts, Kleisli m parts whole) 

Instances

type PureIso whole parts = Iso Identity whole parts

Iso with the Identity monad.

newIso' :: Monad m => (whole -> m parts, parts -> m whole) -> Iso m whole parts

Like 'new2way\'' but make it explicitly an Iso-morphic function. This function is just a convenience so you do not have to provide an explicit type signature.

newIso :: Monad m => (whole -> parts, parts -> whole) -> Iso m whole parts

Like new2way but make it explicitly an Iso-morphic function. This function is just a convenience so you do not have to provide an explicit type signature.

inverse :: (TwoWayClass iso, Monad m) => iso m whole parts -> iso m parts whole

Invert an isomorphism so make becomes un and un becomes make.

un :: TwoWayClass iso => iso Identity whole parts -> whole -> parts

Like un' but uses a PureIso so you do not need to evaluate a Monad, this function automatically evaluates runIdentity.

make :: TwoWayClass iso => iso Identity whole parts -> parts -> whole

Like make' but uses a PureIso so you do not need to evaluate a Monad, this function automatically evaluates runIdentity.

un' :: (TwoWayClass iso, Monad m) => iso m whole parts -> whole -> m parts

An Iso-morphism that takes a type whole and un-makes it, turning the whole into the parts.

make' :: (TwoWayClass iso, Monad m) => iso m whole parts -> parts -> m whole

An Iso-morphism that takes a type parts and makes it into a type whole.

unK :: (TwoWayClass iso, Monad m) => iso m whole parts -> Kleisli m whole parts

Extract the un Kleisli Arrow from the Iso-morphism.

makeK :: (TwoWayClass iso, Monad m) => iso m whole parts -> Kleisli m parts whole

Extract the make Kleisli Arrow from the Iso-morphism.

isoMonad :: (TwoWayClass inner, Monad m, Monad mm) => Iso m (inner mm whole parts) (whole -> mm parts, parts -> mm whole)

An Iso for turning any another Iso into a pair of Monad-ic functions, similar to isoKleisli but exposes the monadic function within the Kleisli function.

isoMonadTrans :: (TwoWayClass iso, Monad oldM, Monad newM) => (forall c. oldM c -> newM c) -> iso oldM whole parts -> iso newM whole parts

Transform the monadic type of the Iso or TwoWay.

(*~*) :: (TwoWayClass iso, Monad m) => iso m whole0 parts0 -> iso m whole1 parts1 -> iso m (whole0, whole1) (parts0, parts1) infixr 3

Similar to the (***) operator in the Control.Arrow module, except only works on Iso-morphisms. In short, this operator takes a left and right parameter and creates a new Iso-morphism that applies the left Iso to the first element of a pair and the right Iso to the second element of the pair.

(+~+) :: (TwoWayClass iso, Monad m) => iso m wholeLeft partsLeft -> iso m wholeRight partsRight -> iso m (Either wholeLeft wholeRight) (Either partsLeft partsRight) infixr 2

Similar to the (+++) operator in the Control.Arrow module, except only works with Iso-morphisms.

isoFirst :: (TwoWayClass iso, Monad m) => iso m whole parts -> iso m (whole, ignored) (parts, ignored)

Similar to the first function in the Control.Arrow module, except only works with Iso-morphisms. Take an Iso-morphism and turn it into a new Iso-morphism that operates only on the first argument of a pair, ignoring the second argument. Also note that: isoFirst >>> isoSecond is the same as isoSecond >>> isoFirst is the same as (*~*).

isoSecond :: (TwoWayClass iso, Monad m) => iso m whole parts -> iso m (ignored, whole) (ignored, parts)

Similar to the second function in the Control.Arrow module, except only works with Iso-morphisms. Take an Iso-morphism and turn it into a new Iso-morphism that operates only on the second argument of a pair, ignoring the first argument. Also note that: isoFirst a >>> isoSecond b is the same thing as isoSecond b >>> isoFirst a is the same thing as a *~* b.

isoMap :: (TwoWayClass iso, Monad m) => iso m box e -> iso m e e -> iso m box box

Create an Iso-morphism that operates on the contents of a box data type by taking the element of type e out of box, applying another Iso-morphic transformation on the element e, then placing the element e back into the box, thus returning a new box.

isoFMap :: (TwoWayClass mapIso, Monad m) => (forall e. Iso m (box e) e) -> mapIso m a b -> mapIso m (box a) (box b)

If you have an Iso-morphism that can wrap and unwrap a value v from any data type F v, then you can turn that data type F into a functor using the Iso-morphism. Let's call F a pseudo-functor, because it does not necessarily need to be functor in the sense that it instantiates Functor, but becomes a functor when we have an Iso-morphism that could treat it as a functor.

This function Operate on a pseudo-functor by providing an Iso-morphism to unbox and box the contents of the functor, then apply an Iso-morphic transformation on the contents of the functor.

twoWayFunctor :: (TwoWayClass iso, Monad m, Functor f) => (forall whole parts. iso Identity whole parts) -> iso m (f whole) (f parts)

Create a new Iso-morphism by applying a given pure Iso-morphism to a Functor.

Two-Way functions

newtype TwoWay m whole parts

For some related data types, such as Double versus Int, or Text versus ByteString, there may seem to be an Iso-morphic relationship between data types as you can convert from one to the other in both directions, however there is information lost in the conversion process.

If information is lost during conversion, then the types are not Iso-morphic. However it may still be useful to define an two-way function that can make use of the Category API, namely function composition of two-way functions.

To prevent you from mixing up truly Iso-morphic functions and functions that just want to take advantage of the convenience of using two-way API functions that can convert back and forth between types, this TwoWay data type is provided. TwoWay instantiates Category, and can be mixed with truly Iso-morphic functions, while making the type explicitly TwoWay.

This is the best way to make explicit which API functions will lose information during conversion, that way people using your API will not use your function expecting that they can (for example) convert from a Double to an Int and then back from an Int to a Double without loosing the information after the decimal point.

You can think of a TwoWay function as IKEA furniture: you can make a whole from it's parts but you are likely missing some of the parts, or you will end up with extra parts that don't go into the whole, and if you un-make the whole you probably won't end up with the same pile of parts you started with.

Constructors

TwoWay (Kleisli m whole parts, Kleisli m parts whole) 

Instances

type PureTwoWay whole parts = TwoWay Identity whole parts

TwoWay with the Identity monad

new2way :: (TwoWayClass iso, Monad m) => (whole -> parts, parts -> whole) -> iso m whole parts

Construct a TwoWay function or Iso-morphism, or any TwoWayClass of function, from a pair of pure functions. It is a good idea to only use this when declaring a top-level function, where you provide an explicit type signature for the TwoWayClass.

new2way' :: (TwoWayClass iso, Monad m) => (whole -> m parts, parts -> m whole) -> iso m whole parts

Construct a TwoWay function or Iso-morphism, or any TwoWayClass of function, from a pair of monadic functions. It is a good idea to only use this when declaring a top-level function, where you provide an explicit type signature for the TwoWayClass.

isoTo2way :: Iso m whole parts -> TwoWay m whole parts

You may construct a TwoWay from an Iso-morphism, but must not make an Iso-morphism from a TwoWay function. Iso-morphisms should be subset of TwoWay functions.

Operations shared by Isos and TwoWays

class TwoWayClass twoWay where

Both TwoWay-morphisms and Iso-morphisms are two-way functions, and so share similar APIs for working with each of these types of fuctions. This type class allows the similar API functions to be used for both Iso-morhpisms and ordinary TwoWay functions.

The isoKleisli function is an Iso-morphism between the twoWay function (the type instantiating this class) and a pair of Kleisli functions, where the first element of the pair converts a value of type whole to a value of type parts, and the second element of the pair converts a value of type parts to a value of type whole.

Note that the pair of Kleisli functions contained within the twoWay type need not be isomorphic, but the isoKleisli function converting between the Kleisli function pair and the twoWay function type must be a genuine Iso-morphism.

Methods

isoKleisli :: (Monad m, Monad mm) => Iso m (twoWay mm whole parts) (Kleisli mm whole parts, Kleisli mm parts whole)

Isos and TwoWay combinators

Sometimes you have an Iso or TwoWay function that nearly operates on the type you need, but not quite. For example, you have an Isomorphism that produces a pair, but you need the Iso to swap the elements of the pair, then you can use swapped.

This section provides several simple Isos and TwoWays that can be composed with other Isos and TwoWays using the Control.Category operators (>>>) and (<<<).

One simple example of how this could be useful: converting temperature values between Farenheight and Celcius, you can compose the functions added and multiplied like so:

c2f :: Monad m => Iso m Rational Rational
c2f = added (negate 32) >>> multiplied (5/9)

Then, to convert from Farenheight to Celcius you use un c2f, and to convert from Celcius to Farenheight, use make c2f. The inverse function is constructed automatically by virtue of the fact that addition and multiplication over Rational numbers are isomorphic functions.

swapped :: Monad m => Iso m (a, b) (b, a)

dyslexic :: Monad m => Iso m (Either a b) (Either b a)

zipped :: Monad m => TwoWay m [(a, b)] ([a], [b])

negated :: (Num a, Monad m) => Iso m a a

parsed :: (Read a, Show a, Monad m) => TwoWay m a String

rounded :: (Real a, Integral a, RealFrac b, Fractional b, Monad m) => TwoWay m a b

floored :: (Real a, Integral a, RealFrac b, Fractional b, Monad m) => TwoWay m a b

ceilinged :: (Real a, Integral a, RealFrac b, Fractional b, Monad m) => TwoWay m a b

added :: (Num a, Monad m) => a -> Iso m a a

multiplied :: (Num a, Fractional a, Monad m) => a -> Iso m a a

type LazyText = Text

A Text data type from the Data.Text.Lazy module.

type StrictText = Text

A Text data type from the Data.Text module.

type LazyByteString = ByteString

A ByteString data type from the Data.Text.Lazy module.

type StrictByteString = ByteString

A ByteString data type from the Data.ByteString module.

Isomorphisms over Monoid, Semigroup and Applicative newtypes

identity :: Monad m => Iso m (Identity a) a

Iso-morphism for the Identity value in the Data.Monoid module.

kleisli :: (Monad m, Monad mm) => Iso m (Kleisli mm a b) (a -> mm b)

Iso-morphism that can make and un-make a Kleisli Arrow.

monoidEndo :: Monad m => Iso m (Endo a) (a -> a)

Iso-morphism for the Endo value in the Data.Monoid module.

endoIdentity :: Monad m => Iso m (a -> a) (a -> Identity a)

Iso-morphism that changes an ordinary Endo-functor into it's equivalent Identity monad.

monoidDual :: Monad m => Iso m (Dual a) a

Iso-morphism for the Dual value in the Data.Monoid module.

monoidSum :: Monad m => Iso m (Sum a) a

monoidProduct :: Monad m => Iso m (Product a) a

monoidFirst :: Monad m => Iso m (First a) (Maybe a)

monoidLast :: Monad m => Iso m (Last a) (Maybe a)

semiFirst :: Monad m => Iso m (First a) a

semiLast :: Monad m => Iso m (Last a) a

semiOption :: Monad m => Iso m (Option a) (Maybe a)

semiMin :: Monad m => Iso m (Min a) a

semiMax :: Monad m => Iso m (Max a) a

apConst :: Monad m => Iso m (Const a b) a

apWrapMonad :: (Monad m, Monad wm) => Iso m (WrappedMonad wm a) (wm a)

apWrapArrow :: (Monad m, Arrow wa) => Iso m (WrappedArrow wa a b) (wa a b)

apZipList :: Monad m => Iso m (ZipList a) [a]