invertible-0.2.0.6: bidirectional arrows, bijective functions, and invariant functors

Safe HaskellNone
LanguageHaskell2010

Data.Invertible.Prelude

Description

The bidirectional "Prelude", which re-exports various bijections similar to functions from Prelude. Most "un"-functions are left out for obvious reasons.

Synopsis

Documentation

(<->) :: BiArrow a => (b -> c) -> (c -> b) -> a b c infix 2 Source #

Take two functions and lift them into a bidirectional arrow. The intention is that these functions are each other's inverse.

type (<->) = Bijection (->) infix 2 Source #

Specialization of Bijection to function arrows. Represents both a function, f, and its (presumed) inverse, g, represented as f :<->: g.

const :: a -> () <-> a Source #

Convert between '()' and a constant (not a true bijection).

flip :: (a -> b -> c) <-> (b -> a -> c) Source #

flip the order of the first two arguments of a function.

id :: a <-> a Source #

Identity bijection.

(.) :: (b <-> c) -> (a <-> b) -> a <-> c infixr 9 Source #

Bijection composition

not :: Bool <-> Bool Source #

Boolean not.

enum :: Enum a => Int <-> a Source #

Convert between an Int and an Enum with toEnum and fromEnum.

succ :: Enum a => a <-> a Source #

Combine succ and pred

fst :: (a, ()) <-> a Source #

Extract the fst component of a pair.

snd :: ((), a) <-> a Source #

Extract the snd component of a pair.

curry :: ((a, b) -> c) <-> (a -> b -> c) Source #

Convert between an uncurried function and a curryed function.

cons :: Maybe (a, [a]) <-> [a] Source #

Convert between Just (head, tail) and the non-empty list head:tail.

uncons :: [a] <-> Maybe (a, [a]) Source #

Convert between the non-empty list head:tail and Just (head, tail). (invert cons)

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

Lift both sides of an bijection over a functor using fmap. We name this bifmap in deference to the more useful fmap.

class Functor f where Source #

An invariant version of Functor, equivalent to Invariant.

Methods

fmap :: (a <-> b) -> f a -> f b Source #

Instances
Functor Endo Source # 
Instance details

Defined in Control.Invertible.Functor

Methods

fmap :: (a <-> b) -> Endo a -> Endo b Source #

Functor BiEndo Source # 
Instance details

Defined in Control.Invertible.Functor

Methods

fmap :: (a <-> b) -> BiEndo a -> BiEndo b Source #

Functor m => Functor (MaybeT m) Source # 
Instance details

Defined in Control.Invertible.Monoidal

Methods

fmap :: (a <-> b) -> MaybeT m a -> MaybeT m b Source #

Functor (Free f) Source # 
Instance details

Defined in Control.Invertible.Monoidal.Free

Methods

fmap :: (a <-> b) -> Free f a -> Free f b Source #

(Semigroupoid a, Arrow a) => Functor (Bijection a b) Source # 
Instance details

Defined in Control.Invertible.Functor

Methods

fmap :: (a0 <-> b0) -> Bijection a b a0 -> Bijection a b b0 Source #

(<$>) :: Functor f => (a <-> b) -> f a -> f b infixl 4 Source #

An infix synnonym for fmap.

map :: (a <-> b) -> [a] <-> [b] Source #

Apply a bijection over a list using map.

reverse :: [a] <-> [a] Source #

reverse the order of a (finite) list.

zip :: ([a], [b]) <-> [(a, b)] Source #

zip two lists together.

zip3 :: ([a], [b], [c]) <-> [(a, b, c)] Source #

zip3 three lists together.

zipWith :: ((a, b) <-> c) -> ([a], [b]) <-> [c] Source #

zipWith two lists together using a bijection.

lines :: String <-> [String] Source #

Split a string into lines.

words :: String <-> [String] Source #

Split a string into words.