profunctor-optics-0.0.0.2: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor.Optic.Index

Contents

Synopsis

Indexing

(%) :: Semigroup i => Representable p => IndexedOptic p i b1 b2 a1 a2 -> IndexedOptic p i c1 c2 b1 b2 -> IndexedOptic p i c1 c2 a1 a2 infixr 8 Source #

Compose two indexed traversals, combining indices.

Its precedence is one lower than that of function composition, which allows . to be nested in %.

If you only need the final index then use .:

>>> ixlists (ixtraversed . ixtraversed) foobar
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]
>>> ixlistsFrom (ixlast ixtraversed % ixlast ixtraversed) (Last 0) foobar & fmapped . t21 ..~ getLast
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]
>>> ixlists (ixtraversed . ixtraversed) exercises
[("crunches",25),("handstands",5),("crunches",20),("pushups",10),("handstands",3),("pushups",15)]
>>> ixlists (ixtraversed % ixtraversed) exercises
[("Fridaycrunches",25),("Fridayhandstands",5),("Mondaycrunches",20),("Mondaypushups",10),("Wednesdayhandstands",3),("Wednesdaypushups",15)]

ixinit :: Profunctor p => IndexedOptic p i s t a b -> IndexedOptic p (First i) s t a b Source #

ixlast :: Profunctor p => IndexedOptic p i s t a b -> IndexedOptic p (Last i) s t a b Source #

reix :: Profunctor p => (i -> j) -> (j -> i) -> IndexedOptic p i s t a b -> IndexedOptic p j s t a b Source #

Map over the indices of an indexed optic.

>>> ixlists (ixtraversed . reix (<>10) id ixtraversed) foobar
[(10,"foo"),(11,"bar"),(10,"baz"),(11,"bip")]

See also reixed.

ixmap :: Profunctor p => (s -> a) -> (b -> t) -> IndexedOptic p i s t a b Source #

withIxrepn :: Representable p => IndexedOptic p i s t a b -> i -> s -> (i -> a -> Rep p b) -> Rep p t Source #

Coindexing

(#) :: Semigroup k => Corepresentable p => CoindexedOptic p k b1 b2 a1 a2 -> CoindexedOptic p k c1 c2 b1 b2 -> CoindexedOptic p k c1 c2 a1 a2 infixr 8 Source #

Compose two coindexed traversals, combining indices.

Its precedence is one lower than that of function composition, which allows . to be nested in #.

If you only need the final index then use .

cxinit :: Profunctor p => CoindexedOptic p k s t a b -> CoindexedOptic p (First k) s t a b Source #

cxlast :: Profunctor p => CoindexedOptic p k s t a b -> CoindexedOptic p (Last k) s t a b Source #

recx :: Profunctor p => (k -> l) -> (l -> k) -> CoindexedOptic p k s t a b -> CoindexedOptic p l s t a b Source #

Map over the indices of a coindexed optic.

See also recxed.

cxmap :: Profunctor p => (s -> a) -> (b -> t) -> CoindexedOptic p k s t a b Source #

cxed :: Strong p => Iso (Cx p s s t) (Cx p k a b) (p s t) (p a b) Source #

cxjoin :: Strong p => Cx p a a b -> p a b Source #

cxreturn :: Profunctor p => p a b -> Cx p k a b Source #

type Cx' p a b = Cx p a a b Source #

cxunit :: Strong p => Cx' p :-> p Source #

cxpastro :: Profunctor p => Iso (Cx' p a b) (Cx' p c d) (Pastro p a b) (Pastro p c d) Source #

cxfirst' :: Profunctor p => Cx' p a b -> Cx' p (a, c) (b, c) Source #

withCxrepn :: Corepresentable p => CoindexedOptic p k s t a b -> Corep p s -> k -> (Corep p a -> k -> b) -> t Source #

Index

data Index a b r Source #

An indexed store that characterizes a Lens

Index a b r ≡ forall f. Functor f => (a -> f b) -> f r,

Constructors

Index a (b -> r) 
Instances
Profunctor (Index a) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Methods

dimap :: (a0 -> b) -> (c -> d) -> Index a b c -> Index a a0 d #

lmap :: (a0 -> b) -> Index a b c -> Index a a0 c #

rmap :: (b -> c) -> Index a a0 b -> Index a a0 c #

(#.) :: Coercible c b => q b c -> Index a a0 b -> Index a a0 c #

(.#) :: Coercible b a0 => Index a b c -> q a0 b -> Index a a0 c #

Functor (Index a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Methods

fmap :: (a0 -> b0) -> Index a b a0 -> Index a b b0 #

(<$) :: a0 -> Index a b b0 -> Index a b a0 #

a ~ b => Foldable (Index a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Methods

fold :: Monoid m => Index a b m -> m #

foldMap :: Monoid m => (a0 -> m) -> Index a b a0 -> m #

foldr :: (a0 -> b0 -> b0) -> b0 -> Index a b a0 -> b0 #

foldr' :: (a0 -> b0 -> b0) -> b0 -> Index a b a0 -> b0 #

foldl :: (b0 -> a0 -> b0) -> b0 -> Index a b a0 -> b0 #

foldl' :: (b0 -> a0 -> b0) -> b0 -> Index a b a0 -> b0 #

foldr1 :: (a0 -> a0 -> a0) -> Index a b a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Index a b a0 -> a0 #

toList :: Index a b a0 -> [a0] #

null :: Index a b a0 -> Bool #

length :: Index a b a0 -> Int #

elem :: Eq a0 => a0 -> Index a b a0 -> Bool #

maximum :: Ord a0 => Index a b a0 -> a0 #

minimum :: Ord a0 => Index a b a0 -> a0 #

sum :: Num a0 => Index a b a0 -> a0 #

product :: Num a0 => Index a b a0 -> a0 #

Sieve (IsoRep a b) (Index a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Iso

Methods

sieve :: IsoRep a b a0 b0 -> a0 -> Index a b b0 #

Sieve (LensRep a b) (Index a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Lens

Methods

sieve :: LensRep a b a0 b0 -> a0 -> Index a b b0 #

values :: Index a b r -> b -> r Source #

info :: Index a b r -> a Source #

Coindex

newtype Coindex a b k Source #

An indexed continuation that characterizes a Grate

Coindex a b k ≡ forall f. Functor f => (f a -> b) -> f k,

See also zipWithFOf.

Coindex can also be used to compose indexed maps, folds, or traversals directly.

For example, using the containers library:

 Coindex mapWithKey :: Coindex (a -> b) (Map k a -> Map k b) k
 Coindex foldMapWithKey :: Monoid m => Coindex (a -> m) (Map k a -> m) k
 Coindex traverseWithKey :: Applicative t => Coindex (a -> t b) (Map k a -> t (Map k b)) k

Constructors

Coindex 

Fields

Instances
Functor (Coindex a b) Source #

Change the Monoid used to combine indices.

Instance details

Defined in Data.Profunctor.Optic.Index

Methods

fmap :: (a0 -> b0) -> Coindex a b a0 -> Coindex a b b0 #

(<$) :: a0 -> Coindex a b b0 -> Coindex a b a0 #

a ~ b => Applicative (Coindex a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Methods

pure :: a0 -> Coindex a b a0 #

(<*>) :: Coindex a b (a0 -> b0) -> Coindex a b a0 -> Coindex a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Coindex a b a0 -> Coindex a b b0 -> Coindex a b c #

(*>) :: Coindex a b a0 -> Coindex a b b0 -> Coindex a b b0 #

(<*) :: Coindex a b a0 -> Coindex a b b0 -> Coindex a b a0 #

a ~ b => Apply (Coindex a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Methods

(<.>) :: Coindex a b (a0 -> b0) -> Coindex a b a0 -> Coindex a b b0 #

(.>) :: Coindex a b a0 -> Coindex a b b0 -> Coindex a b b0 #

(<.) :: Coindex a b a0 -> Coindex a b b0 -> Coindex a b a0 #

liftF2 :: (a0 -> b0 -> c) -> Coindex a b a0 -> Coindex a b b0 -> Coindex a b c #

Cosieve (IsoRep a b) (Coindex a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Iso

Methods

cosieve :: IsoRep a b a0 b0 -> Coindex a b a0 -> b0 #

Cosieve (GrateRep a b) (Coindex a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

cosieve :: GrateRep a b a0 b0 -> Coindex a b a0 -> b0 #

Generic (Coindex a b k) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

Associated Types

type Rep (Coindex a b k) :: Type -> Type #

Methods

from :: Coindex a b k -> Rep (Coindex a b k) x #

to :: Rep (Coindex a b k) x -> Coindex a b k #

type Rep (Coindex a b k) Source # 
Instance details

Defined in Data.Profunctor.Optic.Index

type Rep (Coindex a b k) = D1 (MetaData "Coindex" "Data.Profunctor.Optic.Index" "profunctor-optics-0.0.0.2-AicTFpB8otYHD4MsgkjaSV" True) (C1 (MetaCons "Coindex" PrefixI True) (S1 (MetaSel (Just "runCoindex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((k -> a) -> b))))

trivial :: Coindex a b a -> b Source #

noindex :: Monoid k => (a -> b) -> Coindex a b k Source #

Lift a regular function into a coindexed function.

For example, to traverse two layers, keeping only the first index:

 Coindex mapWithKey ## noindex map
   :: Monoid k =>
      Coindex (a -> b) (Map k (Map j a) -> Map k (Map j b)) k

coindex :: Functor f => k -> (a -> b) -> Coindex (f a) (f b) k Source #

(##) :: Semigroup k => Coindex b c k -> Coindex a b k -> Coindex a c k infixr 9 Source #

Compose two coindexes.

When k is a Monoid, Coindex can be used to compose indexed traversals, folds, etc.

For example, to keep track of only the first index seen, use Data.Monoid.First:

 fmap (First . pure) :: Coindex a b c -> Coindex a b (First c)

or keep track of all indices using a list:

 fmap (:[]) :: Coindex a b c -> Coindex a b [c]