putlenses-0.0.3: Put-based lens library

Stabilityprovisional
MaintainerHugo Pacheco <hpacheco@nii.ac.jp>
Safe HaskellNone

Generics.Putlenses.Language

Description

Core language of put-based lenses.

Synopsis

Documentation

withS :: Putlens st s s v -> Putlens st e s vSource

Modifies the environment to the original source

withMbS :: Putlens st (Maybe s) s v -> Putlens st e s vSource

Modifies the environment to the original source (with Maybe)

withV :: Putlens st v s v -> Putlens st e s vSource

Modifies the environment to the original view

withMbV :: Putlens st (Maybe v) s v -> Putlens st e s vSource

Modifies the environment to the original view (with Maybe)

withV' :: Putlens st v s v -> Putlens st e s vSource

Modifies the environment to the updated view

initSt :: (st -> e -> v -> st') -> Putlens st' e s v -> Putlens st e s vSource

modifySt :: (st -> e -> v -> st) -> Putlens st e s v -> Putlens st e s vSource

Modifies the state before executing put

updateSt :: (st -> e -> s -> st) -> Putlens st e s v -> Putlens st e s vSource

Modifies the state after executing put

modifyS :: Eq v => (st -> e -> s -> v -> s) -> Putlens st e s v -> Putlens st e s vSource

Modifies the original source before executing put (unsafe cast)

modifyV' :: (st -> e -> v -> v) -> Putlens st e s v -> Putlens st e s vSource

Modifies the updated view before executing put (unsafe cast)

updateS' :: (st -> e -> s -> s) -> Putlens st e s v -> Putlens st e s vSource

Modifies the updated source after executing put (unsafe cast)

unforkPut :: Putlens st e s v1 -> Putlens st e s v2 -> Putlens st e 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 :: Putlens st e v vSource

Identity putlens

(.<) :: Putlens st e s u -> Putlens st e u v -> Putlens st e s vSource

Binary composition of putlenses

phiPut :: (v -> Bool) -> Putlens st e v vSource

View-based filtering putlens

botPut :: Putlens st e a bSource

Bottom putlens that is always undefined

addfstPut :: Eq v => (st -> e -> v -> s1) -> Putlens st e (s1, v) vSource

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

addsndPut :: Eq v => (st -> e -> v -> s2) -> Putlens st e (v, s2) vSource

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

keepfstPut :: Eq v => Putlens st e (s1, v) vSource

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

keepsndPut :: Eq v => Putlens st e (v, s2) vSource

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

keepfstOrPut :: Eq v => (st -> e -> v -> s1) -> Putlens st e (s1, v) vSource

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

keepsndOrPut :: Eq v => (st -> e -> v -> s2) -> Putlens st e (v, s2) vSource

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

remfstPut :: Eq v1 => (v -> v1) -> Putlens st e 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 :: Eq v2 => (v -> v2) -> Putlens st e v (v, v2)Source

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

(><<) :: (Eq v1, Eq v2) => Putlens st e s1 v1 -> Putlens st e s2 v2 -> Putlens st e (s1, s2) (v1, v2)Source

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

ignorePut :: Eq v => v -> Putlens st e () vSource

Deletes a user-specified view

newPut :: s -> Putlens st e s ()Source

Creates a constant source from an empty view

keepPut :: Putlens st e s ()Source

Adds a new source (retrieving the original source)

pntPut :: (st -> e -> a) -> Putlens st e a ()Source

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

addfstOnePut :: Eq v => Putlens st e ((), v) vSource

Adds an empty view to the left of the view

addsndOnePut :: Eq v => Putlens st e (v, ()) vSource

Adds an empty view to the right of the view

remfstOnePut :: Putlens st e a ((), a)Source

Deletes an empty view to the left of the view

remsndOnePut :: Putlens st e a (a, ())Source

Deletes an empty view to the left of the view

injPut :: Eq v => (st -> e -> v -> Bool) -> Putlens st e (Either v v) vSource

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

injSPut :: Eq v => Putlens st e (Either v v) vSource

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

(\/<) :: Putlens st e s v1 -> Putlens st e s v2 -> Putlens st e s (Either v1 v2)Source

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

eitherSPut :: (s -> Bool) -> Putlens st e s v1 -> Putlens st e s v2 -> Putlens st e s (Either v1 v2)Source

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

(.\/<) :: Putlens st e s v1 -> Putlens st e s v2 -> Putlens st e s (Either v1 v2)Source

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

(\/.<) :: Putlens st e s v1 -> Putlens st e s v2 -> Putlens st e s (Either v1 v2)Source

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

(-|-<) :: Putlens st e s1 v1 -> Putlens st e s2 v2 -> Putlens st e (Either s1 s2) (Either v1 v2)Source

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

injlPut :: Putlens st e (Either v v2) vSource

Injects a left tag in the view

injrPut :: Putlens st e (Either v1 v) vSource

Injects a right tag in the view

uninjlPut :: Putlens st e v (Either v v2)Source

Ignores left tags for left-tagged views

uninjrPut :: Putlens st e v (Either v1 v)Source

Ignores left tags for left-tagged views

ifthenelsePut :: Eq v => (st -> e -> v -> Bool) -> Putlens st e s v -> Putlens st e s v -> Putlens st e s vSource

Conditional putlens combinator

ifVthenelsePut :: Eq v => (v -> Bool) -> Putlens st e s v -> Putlens st e s v -> Putlens st e s vSource

Conditional putlens combinator (with a predicate on views)

ifSthenelsePut :: Eq v => (s -> Bool) -> Putlens st e s v -> Putlens st e s v -> Putlens st e s vSource

Conditional putlens combinator (with a predicate on sources)

ifKthenelsePut :: (st -> e -> v -> Bool) -> Putlens st e s v -> Putlens st e s v -> Putlens st e s vSource

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 ^ This invariant is not checked

customPut :: Eq v => (st -> Maybe s -> v -> s) -> (s -> v) -> Putlens st e s vSource

Embed user-specified lenses as putlenses

innPut :: InOut a => Putlens st e a (F a)Source

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

outPut :: InOut a => Putlens st e (F a) aSource

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

swapPut :: Putlens st e (b, a) (a, b)Source

Swaps the order of elements in a view pair

assoclPut :: Putlens st e ((a, b), c) (a, (b, c))Source

Associates a right-nested view pair to the left

assocrPut :: Putlens st e (a, (b, c)) ((a, b), c)Source

Associates a left-nested view pair to the right

coswapPut :: Putlens st e (Either b a) (Either a b)Source

Swaps the order of elements in a view sum

coassoclPut :: Putlens st e (Either (Either a b) c) (Either a (Either b c))Source

Associates a right-nested view sum to the left

coassocrPut :: Putlens st e (Either a (Either b c)) (Either (Either a b) c)Source

Associates a left-nested view sum to the left

distlPut :: Putlens st e (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 :: Putlens st e (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 :: Putlens st e (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 :: Putlens st e (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 :: Putlens st e (b, (a, c)) (a, (b, c))Source

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

sublPut :: Putlens st e ((a, c), b) ((a, b), c)Source

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

cosubrPut :: Putlens st e (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 :: Putlens st e (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 :: Putlens st e ((a, c), (b, d)) ((a, b), (c, d))Source

Swaps the order of two nested view pairs

distsPut :: Putlens st e (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

paramfstPut :: (k -> Putlens st e s v) -> Putlens st e (k, s) (k, v)Source

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

paramfstGet :: Eq v => (k -> Putlens st e s v) -> Putlens st e (k, s) vSource

Lifts a left element of the source to an external parameter

paramsndPut :: (k -> Putlens st e s v) -> Putlens st e (s, k) (v, k)Source

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

paramsndGet :: Eq v => (k -> Putlens st e s v) -> Putlens st e (s, k) vSource

Lifts a right element of the source to an external parameter