putlenses-0.0.3: Put-based lens library

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

Generics.Putlenses.Examples.Examples

Contents

Description

Collection of put-based programming examples

Synopsis

Lists

mapPut :: Eq a => Putlens st e b a -> Putlens st e [b] [a]Source

unfoldrPut :: (Eq a, Eq b) => Putlens st e (b, a) a -> a -> Putlens st e [b] aSource

unfoldrSPut :: (Eq a, Eq b) => Putlens st e (b, a) a -> a -> Putlens st e [b] aSource

Constructor/destructor putlenses for lists

nilPut :: Putlens st e [a] ()Source

consPut :: Putlens st e [a] (a, [a])Source

unnilPut :: Putlens st e () [a]Source

unconsPut :: Putlens st e (a, [a]) [a]Source

unheadPut :: Eq a => Putlens st e [a] aSource

untailPut :: Eq a => Putlens st e [a] [a]Source

wrapPut :: Eq a => Putlens st e [a] aSource

unwrapPut :: Eq a => Putlens st e a [a]Source

example of automatically deriving constructor/destructor putlenses for binary trees

data Tree a Source

Constructors

Empty 
Node a (Tree a) (Tree a) 

Instances

unnodePut :: forall st e a. Putlens st e (a, (Tree a, Tree a)) (Tree a)Source

nodePut :: forall st e a. Putlens st e (Tree a) (a, (Tree a, Tree a))Source

unemptyPut :: forall st e a. Putlens st e () (Tree a)Source

emptyPut :: forall st e a. Putlens st e (Tree a) ()Source

List concatenation

catPut :: Eq a => Putlens st e ([a], [a]) [a]Source

List concatenation (positional)

catPutN :: Eq a => (Maybe ([a], [a]) -> [a] -> Int) -> Putlens st e ([a], [a]) [a]Source

List concatenation (split the view list at position n-1)

catPutN' :: Eq a => Putlens Int e ([a], [a]) [a]Source

catPut2 :: Putlens st e ([Integer], [Integer]) [Integer]Source

List concatenation (split the view list in half)

catPutP :: Eq a => (e -> a -> Bool) -> Putlens st e ([a], [a]) [a]Source

List concatenation (puts elements to the left while satisfying a predicate)

catPutSame :: Eq a => Putlens st e ([a], [a]) [a]Source

List concatenation (puts elements to the left while being equal)

catPutPred :: Ord a => a -> Putlens st e ([a], [a]) [a]Source

List concatenation (puts elements to the left while smaller than a particular value)

Integers

Naturals

data Nat Source

Constructors

ZeroN 
SuccN Nat 

Instances

unsuccNPut :: forall st e. Putlens st e Nat NatSource

succNPut :: forall st e. Putlens st e Nat NatSource

unzeroNPut :: forall st e. Putlens st e () NatSource

zeroNPut :: forall st e. Putlens st e Nat ()Source

List length

lengthNatPut :: Eq a => (Int -> a) -> Putlens st e [a] NatSource

Length as a natural number

List lookup

embedAtPut :: Eq a => Int -> Putlens st e [a] aSource

Embeds a value at a fixed position in a list

embedAtPut' :: Eq a => Putlens st e (Int, [a]) aSource

embedAtPut1 :: Eq a => Int -> Putlens st e [a] aSource

Embeds a value at a fixed position in a list (supports extending the length original list)

embedAtPut1' :: Eq a => Putlens st e (Int, [a]) aSource

embedAtPut2 :: Eq a => Int -> Putlens st e [a] aSource

Embeds a value at a fixed position in a list (splitAt approach)

splitAtPut :: Eq a => Putlens st e (Int, [a]) ([a], [a])Source

List summation

splitPut :: Integral a => (st -> a -> a -> a) -> Putlens st e (a, a) aSource

Splits a view number into two summands (by adding an offset to the original first value)

summandsPut1 :: Integral a => Putlens st e [a] aSource

Updates the sum of a list (preserves the original source and appends the difference to the end)

summandsPut2 :: Integral a => Putlens st e [a] aSource

Updates the sum of a list (distributes the difference by dividing it by two at each recursive step) half of the difference is added to the first element of the source, a quarter to the second, and so on until the remainder is 0

summandsPut3 :: Integral a => Putlens st e [a] aSource

Updates the sum of a list (distributes the difference by dividing it by the length of the original list) distributes the difference evenly among original list numbers

summandsPut4 :: Integral a => Putlens st e [a] aSource

Updates the sum of a list (distributes the difference by dividing it by the length of the original list, always preserving the size f the original list even when the view is zero)

Replicate

replicatePut :: Eq a => Putlens st e (a, Int) [a]Source

Replicate

replicateListPut :: Eq a => Putlens st e [(a, Int)] [a]Source

Replicates a list of elements into a sequence of replicated elements

recoverzerosPut :: Eq a => Putlens st e [(a, Int)] [(a, Int)]Source

splitListPut :: Eq a => Putlens st e [[a]] [a]Source

Halve

halvePut :: Eq a => a -> Putlens st e [a] [a]Source

Takes the first half of a list (with a default empty element)

halvePut2 :: Eq a => a -> Putlens st e [a] [a]Source

Takes the first half of a list (using an increasing counter with each consumed element in the forward direction)

halvePut2' :: Eq a => a -> Putlens st e ([a], Int) ([a], Int)Source

halvePut3 :: Eq a => a -> Putlens st e [a] [a]Source

Takes the first half of a list (using a decreasing counter with the size of the input list, decreased 2 by 2, in the forward direction)

halvePut3' :: Eq a => a -> Putlens Int e ([a], Int) [a]Source

isumPut :: Putlens st e [Int] [Int]Source

Incremental summation

Sorting

iunsortPut1 :: Ord a => Putlens st e [a] [a]Source

Insertion sort (put according to the original relative source order)

delPut1 :: Ord a => Putlens st e (a, [a]) [a]Source

iunsortPut2 :: Ord a => Putlens st e [a] [a]Source

Insertion sort (identity backward transformation)

delPut2 :: Ord a => Putlens st e (a, [a]) [a]Source

qsortPut :: Ord a => Putlens st e [a] [a]Source

Quicksort (put according to the original relative source order)

partitionPut :: Ord a => Putlens st e (a, [a]) (a, ([a], [a]))Source

Partition a list into smaller and bigger elements than a given element

catPutNonEmptyRight :: Eq a => Putlens st e ([a], [a]) [a]Source

Maximum segment sum

type Pos = IntSource

segments :: [a] -> [[a]]Source

mssPut :: Putlens st e [Int] IntSource

Updating maximum segment sum when the sum increases, update only the largest segment when the sum decreases, update all segments that surpass the new maximum, from smallest to largest

positionsPut :: Eq a => Putlens st e [a] [(Pos, a)]Source

positionsPut' :: Eq a => Putlens st [(Pos, a)] (Int, [a]) [(Pos, a)]Source

lookupSegPut :: Eq a => Putlens st e (Map Int a, [Int]) [a]Source

maxPut :: (Num a, Ord a) => Putlens Bool e (a, a) aSource

fromListPut :: (Eq a, Ord k) => Putlens st e [(k, a)] (Map k a)Source

toListPut :: (Eq a, Ord k) => Putlens st e (Map k a) [(k, a)]Source