opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Internal.PackMap

Synopsis

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
Profunctor (PackMap a b) Source # 
Instance details

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 #

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

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

ProductProfunctor (PackMap a b) Source # 
Instance details

Defined in Opaleye.Internal.PackMap

Methods

purePP :: b0 -> PackMap a b a0 b0 #

(****) :: PackMap a b a0 (b0 -> c) -> PackMap a b a0 b0 -> PackMap a b a0 c #

empty :: PackMap a b () () #

(***!) :: PackMap a b a0 b0 -> PackMap a b a' b' -> PackMap a b (a0, a') (b0, b') #

SumProfunctor (PackMap a b) Source # 
Instance details

Defined in Opaleye.Internal.PackMap

Methods

(+++!) :: PackMap a b a0 b0 -> PackMap a b a' b' -> PackMap a b (Either a0 a') (Either b0 b') #

Functor (PackMap a b s) Source # 
Instance details

Defined in Opaleye.Internal.PackMap

Methods

fmap :: (a0 -> b0) -> PackMap a b s a0 -> PackMap a b s b0 #

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

Applicative (PackMap a b s) Source # 
Instance details

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 #

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.

type PM a = State (a, Int) Source #

A helpful monad for writing columns in the AST

write :: a -> PM [a] () Source #

run :: PM [a] r -> (r, [a]) Source #

extractAttrPE :: (primExpr -> String -> String) -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr Source #

Make a fresh name for an input value (the variable primExpr type is typically actually a PrimExpr) based on the supplied function and the unique Tag that is used as part of our QueryArr.

Add the fresh name and the input value it refers to to the list in the state parameter.

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 #

iso :: (s -> a) -> (b -> t) -> PackMap a b s t Source #

Like iso. In practice it won't actually be used as an isomorphism, but it seems to be appropriate anyway.