| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Opaleye.Internal.PackMap
Synopsis
- newtype 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 :: (SumProfunctor p, Functor f) => p a (f b) -> p a' (f b') -> p (Either a a') (f (Either b b'))
 - iso :: (s -> a) -> (b -> t) -> PackMap a b s t
 
Documentation
newtype PackMap a b s t Source #
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
| ProductProfunctor (PackMap a b) Source # | |
| SumProfunctor (PackMap a b) Source # | |
| Profunctor (PackMap a b) Source # | |
Defined in Opaleye.Internal.PackMap Methods dimap :: (a0 -> b0) -> (c -> d) -> PackMap a b b0 c -> PackMap a b a0 d # lmap :: (a0 -> b0) -> PackMap a b b0 c -> PackMap a b a0 c # rmap :: (b0 -> c) -> PackMap a b a0 b0 -> PackMap a b a0 c # (#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> PackMap a b a0 b0 -> PackMap a b a0 c # (.#) :: forall a0 b0 c q. Coercible b0 a0 => PackMap a b b0 c -> q a0 b0 -> PackMap a b a0 c #  | |
| Applicative (PackMap a b s) Source # | |
Defined in Opaleye.Internal.PackMap Methods pure :: a0 -> PackMap a b s a0 # (<*>) :: PackMap a b s (a0 -> b0) -> PackMap a b s a0 -> PackMap a b s b0 # liftA2 :: (a0 -> b0 -> c) -> PackMap a b s a0 -> PackMap a b s b0 -> PackMap a b s c # (*>) :: PackMap a b s a0 -> PackMap a b s b0 -> PackMap a b s b0 # (<*) :: PackMap a b s a0 -> PackMap a b s b0 -> PackMap a b s a0 #  | |
| Functor (PackMap a b s) Source # | |
traversePM :: Applicative f => PackMap a b s t -> (a -> f b) -> s -> f t Source #
Replaces the targeted occurrences 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 package.
extractAttrPE :: (primExpr -> String -> String) -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr Source #
extractAttr :: String -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr Source #
As extractAttrPE but ignores the primExpr when making the
 fresh column name and just uses the supplied String and Tag.
eitherFunction :: (SumProfunctor p, Functor f) => p a (f b) -> p a' (f b') -> p (Either a a') (f (Either b b')) Source #