Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype SelectArr a b = QueryArr ((a, Tag) -> (b, Lateral -> PrimQuery -> PrimQuery, Tag))
- type QueryArr = SelectArr
- type Query = SelectArr ()
- productQueryArr :: ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
- simpleQueryArr :: ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
- mapPrimQuery :: (PrimQuery -> PrimQuery) -> SelectArr a b -> SelectArr a b
- runQueryArr :: QueryArr a b -> (a, Tag) -> (b, Lateral -> PrimQuery -> PrimQuery, Tag)
- runSimpleQueryArr :: QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
- runSimpleQueryArrStart :: QueryArr a b -> a -> (b, PrimQuery, Tag)
- runQueryArrUnpack :: Unpackspec a b -> Query a -> ([PrimExpr], PrimQuery, Tag)
- first3 :: (a1 -> b) -> (a1, a2, a3) -> (b, a2, a3)
- 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]
.
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 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 # | |
simpleQueryArr :: ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b Source #
Deprecated: Use productQueryArr
instead. Its name indicates better what it actually does
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 #