| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Opaleye.Internal.PackMap
- data PackMap a b s t = PackMap (forall f. Applicative f => (a -> f b) -> s -> f t)
- traversePM :: Applicative f => PackMap a b s t -> (a -> f b) -> s -> f t
- overPM :: PackMap a b s t -> (a -> b) -> s -> t
- type PM a = State (a, Int)
- new :: PM a String
- write :: a -> PM [a] ()
- run :: PM [a] r -> (r, [a])
- extractAttrPE :: (primExpr -> String -> String) -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr
- extractAttr :: String -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr
- eitherFunction :: Functor f => (a -> f b) -> (a' -> f b') -> Either a a' -> f (Either b b')
Documentation
A PackMap a b s t encodes how an s contains an
updatable sequence of a inside it. Each a in the sequence can
be updated to a b (and the s changes to a t to reflect this
change of type).
PackMap is just like a Traversal from the lens package.
PackMap has a different order of arguments to Traversal because
it typically needs to be made a Profunctor (and indeed
ProductProfunctor) in s and t. It is unclear at this point
whether we want the same Traversal laws to hold or not. Our use
cases may be much more general.
Constructors
| PackMap (forall f. Applicative f => (a -> f b) -> s -> f t) |
Instances
| SumProfunctor (PackMap a b) Source # | |
| ProductProfunctor (PackMap a b) Source # | |
| Profunctor (PackMap a b) Source # | |
| Functor (PackMap a b s) Source # | |
| Applicative (PackMap a b s) Source # | |
traversePM :: Applicative f => PackMap a b s t -> (a -> f b) -> s -> f t Source #
Replaces the targeted occurences of a in s with b (changing
the s to a t in the process). This can be done via an
Applicative action.
traversePM is just like traverse from the lens package.
traversePM used to be called packmap.
overPM :: PackMap a b s t -> (a -> b) -> s -> t Source #
Modify the targeted occurrences of a in s with b (changing
the s to a t in the process).
overPM is just like over from the lens pacakge.
extractAttrPE :: (primExpr -> String -> String) -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr Source #