planet-mitchell-0.1.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

Optic.Iso

Contents

Synopsis

Iso

type Iso s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Profunctor p, Functor f) => p a (f b) -> p s (f t) #

Isomorphism families can be composed with another Lens using (.) and id.

Since every Iso is both a valid Lens and a valid Prism, the laws for those types imply the following laws for an Iso f:

f . from f ≡ id
from f . f ≡ id

Note: Composition with an Iso is index- and measure- preserving.

type Iso' s a = Iso s s a a #

type Iso' = Simple Iso

iso :: (s -> a) -> (b -> t) -> Iso s t a b #

Build a simple isomorphism from a pair of inverse functions.

view (iso f g) ≡ f
view (from (iso f g)) ≡ g
over (iso f g) h ≡ g . h . f
over (from (iso f g)) h ≡ f . h . g

from :: AnIso s t a b -> Iso b a t s #

Invert an isomorphism.

from (from l) ≡ l

under :: AnIso s t a b -> (t -> s) -> b -> a #

The opposite of working over a Setter is working under an isomorphism.

underover . from
under :: Iso s t a b -> (t -> s) -> b -> a

enum :: Enum a => Iso' Int a #

This isomorphism can be used to convert to or from an instance of Enum.

>>> LT^.from enum
0
>>> 97^.enum :: Char
'a'

Note: this is only an isomorphism from the numeric range actually used and it is a bit of a pleasant fiction, since there are questionable Enum instances for Double, and Float that exist solely for [1.0 .. 4.0] sugar and the instances for those and Integer don't cover all values in their range.

curried :: (Profunctor p, Functor f) => p (a -> b -> c) (f (d -> e -> f)) -> p ((a, b) -> c) (f ((d, e) -> f)) #

The canonical isomorphism for currying and uncurrying a function.

curried = iso curry uncurry
>>> (fst^.curried) 3 4
3
>>> view curried fst 3 4
3

uncurried :: (Profunctor p, Functor f) => p ((a, b) -> c) (f ((d, e) -> f)) -> p (a -> b -> c) (f (d -> e -> f)) #

The canonical isomorphism for uncurrying and currying a function.

uncurried = iso uncurry curry
uncurried = from curried
>>> ((+)^.uncurried) (1,2)
3

flipped :: (Profunctor p, Functor f) => p (b -> a -> c) (f (b' -> a' -> c')) -> p (a -> b -> c) (f (a' -> b' -> c')) #

The isomorphism for flipping a function.

>>> ((,)^.flipped) 1 2
(2,1)

Reversing

class Reversing t where #

This class provides a generalized notion of list reversal extended to other containers.

Minimal complete definition

reversing

Methods

reversing :: t -> t #

Instances
Reversing ByteString 
Instance details

Defined in Control.Lens.Internal.Iso

Reversing ByteString 
Instance details

Defined in Control.Lens.Internal.Iso

Reversing Text 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Text -> Text #

Reversing Text 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Text -> Text #

Reversing [a] 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: [a] -> [a] #

Reversing (NonEmpty a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: NonEmpty a -> NonEmpty a #

Reversing (Seq a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Seq a -> Seq a #

Prim a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

Storable a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

Unbox a => Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

Reversing (Vector a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Vector a -> Vector a #

reversed :: Reversing a => Iso' a a #

An Iso between a list, ByteString, Text fragment, etc. and its reversal.

>>> "live" ^. reversed
"evil"
>>> "live" & reversed %~ ('d':)
"lived"

Strict

class Strict lazy strict | lazy -> strict, strict -> lazy where #

Ad hoc conversion between "strict" and "lazy" versions of a structure, such as Text or ByteString.

Minimal complete definition

strict

Methods

strict :: Iso' lazy strict #

Instances
Strict ByteString ByteString 
Instance details

Defined in Control.Lens.Iso

Strict Text Text 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' Text Text0 #

Strict (ST s a) (ST s a) 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (ST s a) (ST0 s a) #

Strict (WriterT w m a) (WriterT w m a) 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (WriterT0 w m a) (WriterT w m a) #

Strict (StateT s m a) (StateT s m a) 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (StateT0 s m a) (StateT s m a) #

Strict (RWST r w s m a) (RWST r w s m a) 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (RWST0 r w s m a) (RWST r w s m a) #

lazy :: Strict lazy strict => Iso' strict lazy #

An Iso between the strict variant of a structure and its lazy counterpart.

lazy = from strict

See http://hackage.haskell.org/package/strict-base-types for an example use.