Safe Haskell | None |
---|---|
Language | Haskell2010 |
Opaleye.Internal.QueryArr
Synopsis
- newtype SelectArr a b = QueryArr {
- unQueryArr :: a -> State Tag (b, PrimQueryArr)
- type QueryArr = SelectArr
- type Query = SelectArr ()
- productQueryArr' :: (a -> State Tag (b, PrimQuery)) -> QueryArr a b
- leftJoinQueryArr' :: (a -> State Tag (b, PrimExpr, PrimQuery)) -> QueryArr a b
- runSimpleQueryArr' :: QueryArr a b -> a -> State Tag (b, PrimQuery)
- runStateQueryArr :: QueryArr a b -> a -> Tag -> (b, PrimQueryArr, Tag)
- stateQueryArr :: (a -> Tag -> (b, PrimQueryArr, Tag)) -> QueryArr a b
- runSimpleQueryArrStart :: QueryArr a b -> a -> (b, PrimQuery, Tag)
- runQueryArrUnpack :: Unpackspec a b -> Query a -> ([PrimExpr], PrimQuery, Tag)
- type Select = SelectArr ()
- lateral :: (i -> Select a) -> SelectArr i a
- viaLateral :: SelectArr i a -> i -> Select a
- bind :: SelectArr i a -> (a -> SelectArr i b) -> SelectArr i b
- arrowApply :: SelectArr (SelectArr i a, i) a
Documentation
newtype SelectArr a b Source #
A parametrised Select
. A SelectArr a b
accepts an argument
of type a
.
SelectArr a b
is analogous to a Haskell function a -> [b]
.
Constructors
QueryArr | |
Fields
|
Instances
Arrow QueryArr Source # | |
Defined in Opaleye.Internal.QueryArr | |
ArrowChoice QueryArr Source # | |
Defined in Opaleye.Internal.QueryArr | |
ArrowApply QueryArr Source # | |
Defined in Opaleye.Internal.QueryArr | |
Profunctor QueryArr Source # | |
Defined in Opaleye.Internal.QueryArr Methods dimap :: (a -> b) -> (c -> d) -> QueryArr b c -> QueryArr a d # lmap :: (a -> b) -> QueryArr b c -> QueryArr a c # rmap :: (b -> c) -> QueryArr a b -> QueryArr a c # (#.) :: forall a b c q. Coercible c b => q b c -> QueryArr a b -> QueryArr a c # (.#) :: forall a b c q. Coercible b a => QueryArr b c -> q a b -> QueryArr a c # | |
ProductProfunctor QueryArr Source # | |
Monad (QueryArr a) Source # | |
Functor (QueryArr a) Source # | |
Applicative (QueryArr a) Source # | |
Defined in Opaleye.Internal.QueryArr | |
Category QueryArr Source # | |
runStateQueryArr :: QueryArr a b -> a -> Tag -> (b, PrimQueryArr, Tag) Source #
stateQueryArr :: (a -> Tag -> (b, PrimQueryArr, Tag)) -> QueryArr a b Source #
runQueryArrUnpack :: Unpackspec a b -> Query a -> ([PrimExpr], PrimQuery, Tag) Source #
type Select = SelectArr () Source #
A SELECT
, i.e. an SQL query which produces a collection of
rows.
Select a
is analogous to a Haskell value [a]
.
viaLateral :: SelectArr i a -> i -> Select a Source #
Convert an arrow argument into a function argument so that it can
be applied inside do
-notation rather than arrow notation.
arrowApply :: SelectArr (SelectArr i a, i) a Source #