Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Select
- data SelectAttrs
- data From = From {}
- data Join = Join {}
- data Semijoin = Semijoin {
- sjType :: SemijoinType
- sjTable :: Select
- sjCriteria :: Select
- data Values = Values {
- vAttrs :: SelectAttrs
- vValues :: [[SqlExpr]]
- data Binary = Binary {}
- data JoinType
- data SemijoinType
- data BinOp
- data Lateral
- data LockStrength = Update
- data Label = Label {}
- data Returning a = Returning a (NonEmpty SqlExpr)
- data Exists = Exists {}
- sqlQueryGenerator :: PrimQueryFold' Void Select
- exists :: Symbol -> Select -> Select
- sql :: ([PrimExpr], PrimQuery' Void, Tag) -> Select
- unit :: Select
- empty :: Void -> select
- oneTable :: t -> [(Lateral, t)]
- baseTable :: TableIdentifier -> [(Symbol, PrimExpr)] -> Select
- product :: NonEmpty (Lateral, Select) -> [PrimExpr] -> Select
- aggregate :: [(Symbol, (Maybe (AggrOp, [OrderExpr], AggrDistinct), Symbol))] -> Select -> Select
- aggrExpr :: Maybe (AggrOp, [OrderExpr], AggrDistinct) -> PrimExpr -> PrimExpr
- distinctOnOrderBy :: Maybe (NonEmpty PrimExpr) -> [OrderExpr] -> Select -> Select
- limit_ :: LimitOp -> Select -> Select
- join :: JoinType -> PrimExpr -> (Lateral, Select) -> (Lateral, Select) -> Select
- semijoin :: SemijoinType -> Select -> Select -> Select
- values :: [Symbol] -> NonEmpty [PrimExpr] -> Select
- binary :: BinOp -> (Select, Select) -> Select
- joinType :: JoinType -> JoinType
- semijoinType :: SemijoinType -> SemijoinType
- binOp :: BinOp -> BinOp
- newSelect :: From
- sqlExpr :: PrimExpr -> SqlExpr
- sqlSymbol :: Symbol -> String
- sqlBinding :: (Symbol, PrimExpr) -> (SqlExpr, Maybe SqlColumn)
- ensureColumns :: [(SqlExpr, Maybe a)] -> NonEmpty (SqlExpr, Maybe a)
- ensureColumnsGen :: (SqlExpr -> a) -> [a] -> NonEmpty a
- label :: String -> Select -> Select
- relExpr :: PrimExpr -> [(Symbol, PrimExpr)] -> Select
- rebind :: Bool -> [(Symbol, PrimExpr)] -> Select -> Select
- forUpdate :: Select -> Select
Documentation
SelectFrom From | |
Table SqlTable | |
RelExpr SqlExpr | A relation-valued expression |
SelectJoin Join | |
SelectSemijoin Semijoin | |
SelectValues Values | |
SelectBinary Binary | |
SelectLabel Label | |
SelectExists Exists |
data SelectAttrs Source #
Star | |
SelectAttrs (NonEmpty (SqlExpr, Maybe SqlColumn)) | |
SelectAttrsStar (NonEmpty (SqlExpr, Maybe SqlColumn)) |
Instances
Show SelectAttrs Source # | |
Defined in Opaleye.Internal.Sql showsPrec :: Int -> SelectAttrs -> ShowS # show :: SelectAttrs -> String # showList :: [SelectAttrs] -> ShowS # |
Semijoin | |
|
Values | |
|
data SemijoinType Source #
Instances
Show SemijoinType Source # | |
Defined in Opaleye.Internal.Sql showsPrec :: Int -> SemijoinType -> ShowS # show :: SemijoinType -> String # showList :: [SemijoinType] -> ShowS # |
data LockStrength Source #
Instances
Show LockStrength Source # | |
Defined in Opaleye.Internal.Sql showsPrec :: Int -> LockStrength -> ShowS # show :: LockStrength -> String # showList :: [LockStrength] -> ShowS # |
aggregate :: [(Symbol, (Maybe (AggrOp, [OrderExpr], AggrDistinct), Symbol))] -> Select -> Select Source #
ensureColumnsGen :: (SqlExpr -> a) -> [a] -> NonEmpty a Source #
For ensuring that we have at least one column in a SELECT or RETURNING