putlenses-0.1.3: Put-based lens library

Copyright(C) 2013 Hugo Pacheco
LicenseBSD-style (see the file LICENSE)
MaintainerHugo Pacheco <hpacheco@nii.ac.jp>
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Generics.Putlenses.Language

Description

Core language of put-based lenses.

Synopsis

Documentation

withMonadPut :: (Monad m, Monad n) => (forall a. Maybe s -> v -> n a -> m a) -> PutlensM n s v -> PutlensM m s v Source

Runs an inner monad n inside a putlens with monad m

withMonadPut' :: (Monad m, Monad n) => (forall a. Maybe s -> Maybe v -> v -> n a -> m a) -> PutlensM n s v -> PutlensM m s v Source

Runs an inner monad n inside a putlens with monad m (using also the original view)

effectPut :: Monad m => (Maybe s -> v -> m ()) -> PutlensM m s v -> PutlensM m s v Source

Applies some monadic modification (like changing a state) to a putlens

runMaybePut :: Monad m => PutlensMaybeM m s v -> PutlensM m s v Source

Converts a putlens with explicitly partial put functions into a normal putlens

runStatePut :: Monad m => (Maybe s -> v -> m st) -> PutlensStateM m st s v -> PutlensM m s v Source

Initializes the monad with a new state

resetStatePut :: Monad m => (Maybe s -> v -> st -> m st') -> PutlensStateM m st' s v -> PutlensStateM m st s v Source

Ignores the current state and initializes a new state monad with a new state

withStatePut :: MonadState st m => (Maybe s -> v -> st -> m st) -> PutlensM m s v -> PutlensM m s v Source

Modifies the state before executing put

withStateTPut :: Monad m => (Maybe s -> v -> st -> m st) -> PutlensStateM m st s v -> PutlensStateM m st s v Source

updateStatePut :: MonadState st m => (Maybe s -> s -> st -> m st) -> PutlensM m s v -> PutlensM m s v Source

Modifies the state after executing put

updateStateTPut :: Monad m => (Maybe s -> s -> st -> m st) -> PutlensStateM m st s v -> PutlensStateM m st s v Source

runReaderPut :: Monad m => (Maybe s -> v -> m e) -> PutlensReaderM m e s v -> PutlensM m s v Source

withReaderPut :: Monad m => (Maybe s -> v -> e -> m e') -> PutlensReaderM m e' s v -> PutlensReaderM m e s v Source

withReaderPut' :: Monad m => (Maybe s -> Maybe v -> v -> e -> m e') -> PutlensReaderM m e' s v -> PutlensReaderM m e s v Source

localPut :: MonadReader e m => (Maybe s -> v -> e -> e) -> PutlensM m s v -> PutlensM m s v Source

withS :: Monad m => PutlensReaderM m s s v -> PutlensReaderM m e s v Source

withMbS :: Monad m => PutlensReaderM m (Maybe s) s v -> PutlensReaderM m e s v Source

withV :: Monad m => PutlensReaderM m v s v -> PutlensReaderM m e s v Source

withMbV :: Monad m => PutlensReaderM m (Maybe v) s v -> PutlensReaderM m e s v Source

withV' :: Monad m => PutlensReaderM m v s v -> PutlensReaderM m e s v Source

modifyS :: (Monad m, Eq v) => (Maybe s -> v -> m (Maybe s)) -> PutlensM m s v -> PutlensM m s v Source

Modifies the original source before executing put (unsafe cast)

modifyV' :: Monad m => (Maybe s -> v -> m v) -> PutlensM m s v -> PutlensM m s v Source

Modifies the updated view before executing put (unsafe cast)

updateS' :: Monad m => (Maybe s -> s -> m s) -> PutlensM m s v -> PutlensM m s v Source

Modifies the updated source after executing put (unsafe cast)

unforkPut :: (Monad m, Eq v1, Eq v2) => PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (v1, v2) Source

Unfork putlens that applies two putlenses to distinct sides of a view pair, producing the same source (unsafe) ^ Dualizes forward splitting and induces a source-passing style

idPut :: Monad m => PutlensM m v v Source

Identity putlens

(.<) :: Monad m => PutlensM m s u -> PutlensM m u v -> PutlensM m s v infixr 9 Source

Binary composition of putlenses

phiPut :: Monad m => (v -> Bool) -> PutlensM m v v Source

View-based filtering putlens

phiSourcePut :: Monad m => (s -> Bool) -> PutlensM m s v -> PutlensM m s v Source

Like phiPut p .< l, but with a less restricted put function that uses the original source even when it does not satisfy p

botPut :: Monad m => PutlensM m a b Source

Bottom putlens that is always undefined

addfstPut :: (Monad m, Eq v) => (Maybe (s1, v) -> v -> m s1) -> PutlensM m (s1, v) v Source

Adds a value to the left of the view (according to a user-specified function)

addfstPutUnsafe :: Monad m => (Maybe (s1, v) -> v -> m s1) -> PutlensM m (s1, v) v Source

addsndPut :: (Monad m, Eq v) => (Maybe (v, s2) -> v -> m s2) -> PutlensM m (v, s2) v Source

Adds a value to the right of the view (according to a user-specified function)

addsndPutUnsafe :: Monad m => (Maybe (v, s2) -> v -> m s2) -> PutlensM m (v, s2) v Source

dupPut :: (Monad m, Eq v) => PutlensM m (v, v) v Source

Duplicates a view by enforcing the two sources to be the same

mergePut :: (Monad m, Eq v) => PutlensM m (v, v) v Source

Duplicates a view but not enforcing the two sources to be the same

keepfstPut :: Monad m => PutlensM m (s1, v) v Source

Adds a value to the left of the view (retrieving it from the original source)

keepsndPut :: Monad m => PutlensM m (v, s2) v Source

Adds a value to the right of the view (retrieving it from the original source)

keepfstOrPut :: Monad m => (v -> m s1) -> PutlensM m (s1, v) v Source

Adds a value to the left of the view (retrieving it from the original source or otherwise using a user-specified function) GetPut is always satisfied

keepsndOrPut :: Monad m => (v -> m s2) -> PutlensM m (v, s2) v Source

Adds a value to the right of the view (retrieving it from the original source or otherwise using a user-specified function) GetPut is always satisfied

remfstPut :: (Monad m, Eq v1) => (v -> v1) -> PutlensM m v (v1, v) Source

Deletes the left value of a view pair (taking a user-specified function that instructs how it can be restored)

remsndPut :: (Monad m, Eq v2) => (v -> v2) -> PutlensM m v (v, v2) Source

Deletes the right value of a view pair (taking a user-specified function that instructs how it can be restored)

(><<) :: Monad m => PutlensM m s1 v1 -> PutlensM m s2 v2 -> PutlensM m (s1, s2) (v1, v2) infix 7 Source

Product putlens that applies two putlenses to distinct sides of a view pair, producing a source pair

(><<<) :: (Monad m, Eq v1, Eq v2) => PutlensM m s1 v1 -> PutlensM m s2 v2 -> PutlensM m (s1, s2) (v1, v2) infix 7 Source

Product putlens that applies two putlenses to distinct sides of a view pair, producing a source pair. | Turns off/on GetPut checking for maximum expressivity.

ignorePut :: (Monad m, Eq v) => v -> PutlensM m () v Source

Deletes a user-specified view

newPut :: Monad m => s -> PutlensM m s () Source

Creates a constant source from an empty view

keepPut :: Monad m => PutlensM m s () Source

Adds a new source (retrieving the original source)

keepOrPut :: Monad m => m s -> PutlensM m s () Source

pntPut :: Monad m => (Maybe a -> m a) -> PutlensM m a () Source

Creates a source from an empty view (according to a user-specified function)

addfstOnePut :: Monad m => PutlensM m ((), v) v Source

Adds an empty view to the left of the view

addsndOnePut :: Monad m => PutlensM m (v, ()) v Source

Adds an empty view to the right of the view

remfstOnePut :: Monad m => PutlensM m a ((), a) Source

Deletes an empty view to the left of the view

remsndOnePut :: Monad m => PutlensM m a (a, ()) Source

Deletes an empty view to the left of the view

injPut :: (Monad m, Eq v) => (Maybe (Either v v) -> v -> m Bool) -> PutlensM m (Either v v) v Source

Injects a tag in the view (according to a user-specified predicate)

injPutUnsafe :: Monad m => (Maybe (Either v v) -> v -> m Bool) -> PutlensM m (Either v v) v Source

injsOrPut :: Monad m => (v -> m Bool) -> PutlensM m (Either v v) v Source

Injects a tag in the view (according to the tags of the original source)

injlsPut :: Monad m => PutlensM m (Either v v) v Source

Injects a tag in the view (according to the tags of the original source) with a left default for create

injrsPut :: Monad m => PutlensM m (Either v v) v Source

Injects a tag in the view (according to the tags of the original source) with a right default for create

injunionPut :: (Eq v, MonadPlus m) => PutlensM m s1 v -> PutlensM m s2 v -> PutlensM m (Either s1 s2) v Source

Injects a tag in the view according to the tags of the original source or giving preference to the first lens when both are applicable. Requires the monad to be an instance of MonadPlus to recover from failure.

injunionPutUnsafe :: MonadPlus m => PutlensM m s1 v -> PutlensM m s2 v -> PutlensM m (Either s1 s2) v Source

(\/<) :: Monad m => PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (Either v1 v2) infix 4 Source

Ignores the tags in the view ^ Fails whenever the domains of getM f and getM g are not disjoint

eitherPutUnsafe :: Monad m => PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (Either v1 v2) Source

eitherSPut :: Monad m => (s -> Bool) -> PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (Either v1 v2) Source

Ignores the tags in the view (guaranteeing disjointness according to a predicate on sources)

(.\/<) :: Monad m => PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (Either v1 v2) infix 4 Source

Ignores the tags in the view (left-biased) ^ Guarantees disjointness by favoring the left putlens

(\/.<) :: Monad m => PutlensM m s v1 -> PutlensM m s v2 -> PutlensM m s (Either v1 v2) infix 4 Source

Ignores the tags in the view (right-biased) ^ Guarantees disjointness by favoring the right putlens

(-|-<) :: Monad m => PutlensM m s1 v1 -> PutlensM m s2 v2 -> PutlensM m (Either s1 s2) (Either v1 v2) infix 5 Source

Sum putlens that applies two putlenses to distinct sides of a view sum, producing a view sum

injlPut :: Monad m => PutlensM m (Either v v2) v Source

Injects a left tag in the view

injrPut :: Monad m => PutlensM m (Either v1 v) v Source

Injects a right tag in the view

uninjlPut :: Monad m => PutlensM m v (Either v v2) Source

Ignores left tags for left-tagged views

uninjrPut :: Monad m => PutlensM m v (Either v1 v) Source

Ignores left tags for left-tagged views

ifthenelsePut :: (Monad m, Eq v) => (Maybe s -> v -> m Bool) -> PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Conditional putlens combinator

ifVthenelsePut :: Monad m => (v -> Bool) -> PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Conditional putlens combinator (with a predicate on views)

ifSthenelsePut :: (Monad m, Eq v) => (s -> Bool) -> PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Conditional putlens combinator (with a predicate on sources)

ifKthenelsePut :: (Monad m, Eq v) => (Maybe s -> v -> m Bool) -> PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Special if-then-else combinator for two putlenses with the same get function ^ Given the invariant |getM f = getM g|, there are no restrictions regarding branching behavior

unionPut :: (Eq v, MonadPlus m) => PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Union of two putlenses (requires the monad to be an instance of MonadPlus to be able to recover from failure)

unionPutUnsafe :: MonadPlus m => PutlensM m s v -> PutlensM m s v -> PutlensM m s v Source

Union of two putlenses (without well-behavedness checks)

customPut :: (Monad m, Eq v) => (Maybe s -> v -> m s) -> (s -> v) -> PutlensM m s v Source

Embed user-specified lenses as putlenses

innPut :: (Monad m, InOut a) => PutlensM m a (F a) Source

Putlens from a sums-of-products view to an algebraic data type source

outPut :: (Monad m, InOut a) => PutlensM m (F a) a Source

Putlens from an algebraic data type view to a sums-of-products source

swapPut :: Monad m => PutlensM m (b, a) (a, b) Source

Swaps the order of elements in a view pair

assoclPut :: Monad m => PutlensM m ((a, b), c) (a, (b, c)) Source

Associates a right-nested view pair to the left

assocrPut :: Monad m => PutlensM m (a, (b, c)) ((a, b), c) Source

Associates a left-nested view pair to the right

coswapPut :: Monad m => PutlensM m (Either b a) (Either a b) Source

Swaps the order of elements in a view sum

coassoclPut :: Monad m => PutlensM m (Either (Either a b) c) (Either a (Either b c)) Source

Associates a right-nested view sum to the left

coassocrPut :: Monad m => PutlensM m (Either a (Either b c)) (Either (Either a b) c) Source

Associates a left-nested view sum to the left

distlPut :: Monad m => PutlensM m (Either (a, c) (b, c)) (Either a b, c) Source

Distributes a sum to the left of a view pair into a sum of pairs

distrPut :: Monad m => PutlensM m (Either (a, b) (a, c)) (a, Either b c) Source

Distributes a sum to the right of a view pair into a sum of pairs

undistlPut :: Monad m => PutlensM m (Either a b, c) (Either (a, c) (b, c)) Source

Undistributes a sum of pairs view into source pair with a sum to the left

undistrPut :: Monad m => PutlensM m (a, Either b c) (Either (a, b) (a, c)) Source

Undistributes a sum of pairs view into source pair with a sum to the right

subrPut :: Monad m => PutlensM m (b, (a, c)) (a, (b, c)) Source

Swaps the first with the second element of a right-nested view pair

sublPut :: Monad m => PutlensM m ((a, c), b) ((a, b), c) Source

Swaps the second with the third element of a left-nested view pair

cosubrPut :: Monad m => PutlensM m (Either b (Either a c)) (Either a (Either b c)) Source

Swaps the first with the second choice of a right-nested view sum

cosublPut :: Monad m => PutlensM m (Either (Either a c) b) (Either (Either a b) c) Source

Swaps the second with the third choice of a left-nested view sum

distpPut :: Monad m => PutlensM m ((a, c), (b, d)) ((a, b), (c, d)) Source

Swaps the order of two nested view pairs

distsPut :: Monad m => PutlensM m (Either (Either (a, c) (a, d)) (Either (b, c) (b, d))) (Either a b, Either c d) Source

Distributes a pair of view sums into a sum of choices

undistsPut :: Monad m => PutlensM m (Either a b, Either c d) (Either (Either (a, c) (a, d)) (Either (b, c) (b, d))) Source

Joins a a sum of choices into a pair of view sums

paramfstPut :: Monad m => (k -> PutlensM m s v) -> PutlensM m (k, s) (k, v) Source

Lifts a parameter outside of a lens (first element as external parameter)

paramfstGet :: (Monad m, Eq v) => (v -> m k) -> (k -> PutlensM m s v) -> PutlensM m (k, s) v Source

Lifts a left element of the source to an external parameter

paramsndPut :: Monad m => (k -> PutlensM m s v) -> PutlensM m (s, k) (v, k) Source

Lifts a parameter outside of a lens (second element as external parameter)

paramsndGet :: (Monad m, Eq v) => (v -> m k) -> (k -> PutlensM m s v) -> PutlensM m (s, k) v Source

Lifts a right element of the source to an external parameter

paramSrcPut :: Monad m => (Maybe s -> k) -> (k -> PutlensM m s v) -> PutlensM m s v Source

paramPut :: Monad m => (Maybe s -> v -> m k) -> (k -> PutlensM m s v) -> PutlensM m s v Source

Lifts a parameter used only by the backward function to an external parameter

isoPut :: Monad m => (a -> b) -> (b -> a) -> PutlensM m b a Source