pointless-lenses-0.0.7: Pointless Lenses library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.Lenses.Examples.Recs

Contents

Description

Pointless Lenses: bidirectional lenses with point-free programming

This module provides specialized versions of recursion patterns to avoid using the internal classes and type families. These functions are more efficient and better for profiling and runtime tests.

Synopsis

Documentation

innList :: Either One (a, [a]) -> [a]Source

outList :: [a] -> Either One (a, [a])Source

innList_lns :: Lens (Either One (a, [a])) [a]Source

outList_lns :: Lens [a] (Either One (a, [a]))Source

outNeList :: NeList a b -> Either a (b, NeList a b)Source

innNeList :: Either a (b, NeList a b) -> NeList a bSource

cataList :: (Either One (a, b) -> b) -> [a] -> bSource

anaList :: (b -> Either One (a, b)) -> b -> [a]Source

fmapList :: (x -> y) -> Either z (a, x) -> Either z (a, y)Source

fmapNat :: (x -> y) -> Either a x -> Either a ySource

fzipList :: (a -> c) -> (Either z (x, a), Either z (x, c)) -> Either z (x, (a, c))Source

fzipNat :: (a -> c) -> (Either z a, Either z c) -> Either z (a, c)Source

cataList_lns :: Lens (Either One (a, b)) b -> Lens [a] bSource

hyloList :: (Either x (y, c) -> c) -> (a -> Either x (y, a)) -> a -> cSource

data NeNat a Source

Constructors

NNil a 
NCons (NeNat a) 

cataNeNat :: (Either a c -> c) -> NeNat a -> cSource

anaNeNat :: (c -> Either a c) -> c -> NeNat aSource

accumNeNat :: ((Either a y, x) -> y) -> ((Either a (NeNat a), x) -> Either a (NeNat a, x)) -> (NeNat a, x) -> ySource

hyloNeNat_lns :: Lens (Either x b) b -> Lens a (Either x a) -> Lens a bSource

data NeList a b Source

Constructors

NeNil a 
NeCons b (NeList a b) 

cataNeList :: (Either a (b, c) -> c) -> NeList a b -> cSource

anaNeList :: (c -> Either a (b, c)) -> c -> NeList a bSource

accumNeList :: ((Either a (b, y), x) -> y) -> ((Either a (b, NeList a b), x) -> Either a (b, (NeList a b, x))) -> (NeList a b, x) -> ySource

cataNeList_lns :: Lens (Either a (b, c)) c -> Lens (NeList a b) cSource

anaNeList_lns :: Lens c (Either a (b, c)) -> Lens c (NeList a b)Source

hyloNeList_lns :: Lens (Either x (y, b)) b -> Lens a (Either x (y, a)) -> Lens a bSource

Examples

cat_pf :: Lens ([a], [a]) [a]Source

concat_pf :: Lens [[a]] [a]Source

map_pf :: Lens a b -> Lens [a] [b]Source