-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | An SQL-generating DSL targeting PostgreSQL -- -- An SQL-generating DSL targeting PostgreSQL. Allows Postgres queries to -- be written within Haskell in a typesafe and composable fashion. @package opaleye @version 0.5.1.1 module Opaleye.Internal.Tag newtype Tag UnsafeTag :: Int -> Tag start :: Tag next :: Tag -> Tag unsafeUnTag :: Tag -> Int tagWith :: Tag -> String -> String instance GHC.Show.Show Opaleye.Internal.Tag.Tag instance GHC.Read.Read Opaleye.Internal.Tag.Tag module Opaleye.Internal.HaskellDB.Sql data SqlTable SqlTable :: Maybe String -> String -> SqlTable [sqlTableSchemaName] :: SqlTable -> Maybe String [sqlTableName] :: SqlTable -> String newtype SqlColumn SqlColumn :: String -> SqlColumn -- | A valid SQL name for a parameter. type SqlName = String data SqlOrderNulls SqlNullsFirst :: SqlOrderNulls SqlNullsLast :: SqlOrderNulls data SqlOrderDirection SqlAsc :: SqlOrderDirection SqlDesc :: SqlOrderDirection data SqlOrder SqlOrder :: SqlOrderDirection -> SqlOrderNulls -> SqlOrder [sqlOrderDirection] :: SqlOrder -> SqlOrderDirection [sqlOrderNulls] :: SqlOrder -> SqlOrderNulls -- | Expressions in SQL statements. data SqlExpr ColumnSqlExpr :: SqlColumn -> SqlExpr CompositeSqlExpr :: SqlExpr -> String -> SqlExpr BinSqlExpr :: String -> SqlExpr -> SqlExpr -> SqlExpr PrefixSqlExpr :: String -> SqlExpr -> SqlExpr PostfixSqlExpr :: String -> SqlExpr -> SqlExpr FunSqlExpr :: String -> [SqlExpr] -> SqlExpr -- | Aggregate functions separate from normal functions. AggrFunSqlExpr :: String -> [SqlExpr] -> [(SqlExpr, SqlOrder)] -> SqlExpr ConstSqlExpr :: String -> SqlExpr CaseSqlExpr :: (NonEmpty (SqlExpr, SqlExpr)) -> SqlExpr -> SqlExpr ListSqlExpr :: [SqlExpr] -> SqlExpr ParamSqlExpr :: (Maybe SqlName) -> SqlExpr -> SqlExpr PlaceHolderSqlExpr :: SqlExpr ParensSqlExpr :: SqlExpr -> SqlExpr CastSqlExpr :: String -> SqlExpr -> SqlExpr DefaultSqlExpr :: SqlExpr ArraySqlExpr :: [SqlExpr] -> SqlExpr -- | Data type for SQL UPDATE statements. data SqlUpdate SqlUpdate :: SqlTable -> [(SqlColumn, SqlExpr)] -> [SqlExpr] -> SqlUpdate -- | Data type for SQL DELETE statements. data SqlDelete SqlDelete :: SqlTable -> [SqlExpr] -> SqlDelete data SqlInsert SqlInsert :: SqlTable -> [SqlColumn] -> (NonEmpty [SqlExpr]) -> SqlInsert instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlExpr instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlOrder instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlOrderDirection instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlOrderNulls instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlColumn instance GHC.Show.Show Opaleye.Internal.HaskellDB.Sql.SqlTable module Opaleye.Internal.HaskellDB.Sql.Print deliteral :: SqlExpr -> SqlExpr ppUpdate :: SqlUpdate -> Doc ppDelete :: SqlDelete -> Doc ppInsert :: SqlInsert -> Doc ppSqlExpr :: SqlExpr -> Doc ppWhere :: [SqlExpr] -> Doc ppGroupBy :: [SqlExpr] -> Doc ppOrderBy :: [(SqlExpr, SqlOrder)] -> Doc ppTable :: SqlTable -> Doc ppAs :: Maybe String -> Doc -> Doc commaV :: (a -> Doc) -> [a] -> Doc commaH :: (a -> Doc) -> [a] -> Doc module Opaleye.Internal.Helpers (.:) :: (r -> z) -> (a -> b -> r) -> a -> b -> z infixr 8 .: (.:.) :: (r -> z) -> (a -> b -> c -> r) -> a -> b -> c -> z infixr 8 .:. (.::) :: (r -> z) -> (a -> b -> c -> d -> r) -> a -> b -> c -> d -> z infixr 8 .:: (.::.) :: (r -> z) -> (a -> b -> c -> d -> e -> r) -> a -> b -> c -> d -> e -> z infixr 8 .::. module Opaleye.Internal.HaskellDB.PrimQuery type TableName = String type Attribute = String type Name = String type Scheme = [Attribute] type Assoc = [(Attribute, PrimExpr)] data Symbol Symbol :: String -> Tag -> Symbol data PrimExpr AttrExpr :: Symbol -> PrimExpr BaseTableAttrExpr :: Attribute -> PrimExpr -- | Composite Type Query CompositeExpr :: PrimExpr -> Attribute -> PrimExpr BinExpr :: BinOp -> PrimExpr -> PrimExpr -> PrimExpr UnExpr :: UnOp -> PrimExpr -> PrimExpr AggrExpr :: AggrOp -> PrimExpr -> [OrderExpr] -> PrimExpr ConstExpr :: Literal -> PrimExpr CaseExpr :: [(PrimExpr, PrimExpr)] -> PrimExpr -> PrimExpr ListExpr :: [PrimExpr] -> PrimExpr ParamExpr :: (Maybe Name) -> PrimExpr -> PrimExpr FunExpr :: Name -> [PrimExpr] -> PrimExpr -- | Cast an expression to a given type. CastExpr :: Name -> PrimExpr -> PrimExpr DefaultInsertExpr :: PrimExpr -- | ARRAY[..] ArrayExpr :: [PrimExpr] -> PrimExpr data Literal NullLit :: Literal -- | represents a default value DefaultLit :: Literal BoolLit :: Bool -> Literal StringLit :: String -> Literal ByteStringLit :: ByteString -> Literal IntegerLit :: Integer -> Literal DoubleLit :: Double -> Literal -- | used for hacking in custom SQL OtherLit :: String -> Literal data BinOp (:==) :: BinOp (:<) :: BinOp (:<=) :: BinOp (:>) :: BinOp (:>=) :: BinOp (:<>) :: BinOp OpAnd :: BinOp OpOr :: BinOp OpLike :: BinOp OpIn :: BinOp OpOther :: String -> BinOp (:||) :: BinOp (:+) :: BinOp (:-) :: BinOp (:*) :: BinOp (:/) :: BinOp OpMod :: BinOp (:~) :: BinOp (:&) :: BinOp (:|) :: BinOp (:^) :: BinOp (:=) :: BinOp OpAtTimeZone :: BinOp (:->) :: BinOp (:->>) :: BinOp (:#>) :: BinOp (:#>>) :: BinOp (:@>) :: BinOp (:<@) :: BinOp (:?) :: BinOp (:?|) :: BinOp (:?&) :: BinOp data UnOp OpNot :: UnOp OpIsNull :: UnOp OpIsNotNull :: UnOp OpLength :: UnOp OpAbs :: UnOp OpNegate :: UnOp OpLower :: UnOp OpUpper :: UnOp UnOpOther :: String -> UnOp data AggrOp AggrCount :: AggrOp AggrSum :: AggrOp AggrAvg :: AggrOp AggrMin :: AggrOp AggrMax :: AggrOp AggrStdDev :: AggrOp AggrStdDevP :: AggrOp AggrVar :: AggrOp AggrVarP :: AggrOp AggrBoolOr :: AggrOp AggrBoolAnd :: AggrOp AggrArr :: AggrOp AggrStringAggr :: PrimExpr -> AggrOp AggrOther :: String -> AggrOp data OrderExpr OrderExpr :: OrderOp -> PrimExpr -> OrderExpr data OrderNulls NullsFirst :: OrderNulls NullsLast :: OrderNulls data OrderDirection OpAsc :: OrderDirection OpDesc :: OrderDirection data OrderOp OrderOp :: OrderDirection -> OrderNulls -> OrderOp [orderDirection] :: OrderOp -> OrderDirection [orderNulls] :: OrderOp -> OrderNulls instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.AggrOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.AggrOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.PrimExpr instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.PrimExpr instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.OrderExpr instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.OrderExpr instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.OrderOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.OrderOp instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.OrderDirection instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.OrderDirection instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.OrderNulls instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.OrderNulls instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.UnOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.UnOp instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.BinOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.BinOp instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.Literal instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.Literal instance GHC.Show.Show Opaleye.Internal.HaskellDB.PrimQuery.Symbol instance GHC.Read.Read Opaleye.Internal.HaskellDB.PrimQuery.Symbol module Opaleye.Internal.PrimQuery data LimitOp LimitOp :: Int -> LimitOp OffsetOp :: Int -> LimitOp LimitOffsetOp :: Int -> Int -> LimitOp data BinOp Except :: BinOp ExceptAll :: BinOp Union :: BinOp UnionAll :: BinOp Intersect :: BinOp IntersectAll :: BinOp data JoinType LeftJoin :: JoinType RightJoin :: JoinType FullJoin :: JoinType data TableIdentifier TableIdentifier :: Maybe String -> String -> TableIdentifier [tiSchemaName] :: TableIdentifier -> Maybe String [tiTableName] :: TableIdentifier -> String tiToSqlTable :: TableIdentifier -> SqlTable data PrimQuery' a Unit :: PrimQuery' a Empty :: a -> PrimQuery' a BaseTable :: TableIdentifier -> [(Symbol, PrimExpr)] -> PrimQuery' a Product :: (NonEmpty (PrimQuery' a)) -> [PrimExpr] -> PrimQuery' a Aggregate :: [(Symbol, (Maybe (AggrOp, [OrderExpr]), PrimExpr))] -> (PrimQuery' a) -> PrimQuery' a Order :: [OrderExpr] -> (PrimQuery' a) -> PrimQuery' a Limit :: LimitOp -> (PrimQuery' a) -> PrimQuery' a Join :: JoinType -> PrimExpr -> (PrimQuery' a) -> (PrimQuery' a) -> PrimQuery' a Values :: [Symbol] -> (NonEmpty [PrimExpr]) -> PrimQuery' a Binary :: BinOp -> [(Symbol, (PrimExpr, PrimExpr))] -> (PrimQuery' a, PrimQuery' a) -> PrimQuery' a Label :: String -> (PrimQuery' a) -> PrimQuery' a RelExpr :: PrimExpr -> [(Symbol, PrimExpr)] -> PrimQuery' a type PrimQuery = PrimQuery' () type PrimQueryFold = PrimQueryFold' () data PrimQueryFold' a p PrimQueryFold :: p -> (a -> p) -> (TableIdentifier -> [(Symbol, PrimExpr)] -> p) -> (NonEmpty p -> [PrimExpr] -> p) -> ([(Symbol, (Maybe (AggrOp, [OrderExpr]), PrimExpr))] -> p -> p) -> ([OrderExpr] -> p -> p) -> (LimitOp -> p -> p) -> (JoinType -> PrimExpr -> p -> p -> p) -> ([Symbol] -> (NonEmpty [PrimExpr]) -> p) -> (BinOp -> [(Symbol, (PrimExpr, PrimExpr))] -> (p, p) -> p) -> (String -> p -> p) -> (PrimExpr -> [(Symbol, PrimExpr)] -> p) -> PrimQueryFold' a p [unit] :: PrimQueryFold' a p -> p [empty] :: PrimQueryFold' a p -> a -> p [baseTable] :: PrimQueryFold' a p -> TableIdentifier -> [(Symbol, PrimExpr)] -> p [product] :: PrimQueryFold' a p -> NonEmpty p -> [PrimExpr] -> p [aggregate] :: PrimQueryFold' a p -> [(Symbol, (Maybe (AggrOp, [OrderExpr]), PrimExpr))] -> p -> p [order] :: PrimQueryFold' a p -> [OrderExpr] -> p -> p [limit] :: PrimQueryFold' a p -> LimitOp -> p -> p [join] :: PrimQueryFold' a p -> JoinType -> PrimExpr -> p -> p -> p [values] :: PrimQueryFold' a p -> [Symbol] -> (NonEmpty [PrimExpr]) -> p [binary] :: PrimQueryFold' a p -> BinOp -> [(Symbol, (PrimExpr, PrimExpr))] -> (p, p) -> p [label] :: PrimQueryFold' a p -> String -> p -> p -- | A relation-valued expression [relExpr] :: PrimQueryFold' a p -> PrimExpr -> [(Symbol, PrimExpr)] -> p primQueryFoldDefault :: PrimQueryFold' a (PrimQuery' a) foldPrimQuery :: PrimQueryFold' a p -> PrimQuery' a -> p times :: PrimQuery -> PrimQuery -> PrimQuery restrict :: PrimExpr -> PrimQuery -> PrimQuery isUnit :: PrimQuery' a -> Bool instance GHC.Show.Show a => GHC.Show.Show (Opaleye.Internal.PrimQuery.PrimQuery' a) instance GHC.Show.Show Opaleye.Internal.PrimQuery.TableIdentifier instance GHC.Show.Show Opaleye.Internal.PrimQuery.JoinType instance GHC.Show.Show Opaleye.Internal.PrimQuery.BinOp instance GHC.Show.Show Opaleye.Internal.PrimQuery.LimitOp module Opaleye.Internal.Label label' :: String -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag) module Opaleye.Internal.Optimize optimize :: PrimQuery' a -> PrimQuery' a removeUnit :: PrimQuery' a -> PrimQuery' a mergeProduct :: PrimQuery' a -> PrimQuery' a removeEmpty :: PrimQuery' a -> Maybe (PrimQuery' b) module Opaleye.Internal.HaskellDB.Sql.Generate data SqlGenerator SqlGenerator :: (SqlTable -> [PrimExpr] -> Assoc -> SqlUpdate) -> (SqlTable -> [PrimExpr] -> SqlDelete) -> (SqlTable -> [Attribute] -> NonEmpty [PrimExpr] -> SqlInsert) -> (PrimExpr -> SqlExpr) -> (Literal -> String) -> (String -> String) -> SqlGenerator [sqlUpdate] :: SqlGenerator -> SqlTable -> [PrimExpr] -> Assoc -> SqlUpdate [sqlDelete] :: SqlGenerator -> SqlTable -> [PrimExpr] -> SqlDelete [sqlInsert] :: SqlGenerator -> SqlTable -> [Attribute] -> NonEmpty [PrimExpr] -> SqlInsert [sqlExpr] :: SqlGenerator -> PrimExpr -> SqlExpr [sqlLiteral] :: SqlGenerator -> Literal -> String -- | Turn a string into a quoted string. Quote characters and any escaping -- are handled by this function. [sqlQuote] :: SqlGenerator -> String -> String module Opaleye.Internal.HaskellDB.Sql.Default mkSqlGenerator :: SqlGenerator -> SqlGenerator defaultSqlGenerator :: SqlGenerator toSqlOrder :: SqlGenerator -> OrderExpr -> (SqlExpr, SqlOrder) toSqlColumn :: Attribute -> SqlColumn toSqlAssoc :: SqlGenerator -> Assoc -> [(SqlColumn, SqlExpr)] defaultSqlUpdate :: SqlGenerator -> SqlTable -> [PrimExpr] -> Assoc -> SqlUpdate defaultSqlInsert :: SqlGenerator -> SqlTable -> [Attribute] -> NonEmpty [PrimExpr] -> SqlInsert defaultSqlDelete :: SqlGenerator -> SqlTable -> [PrimExpr] -> SqlDelete defaultSqlExpr :: SqlGenerator -> PrimExpr -> SqlExpr showBinOp :: BinOp -> String data UnOpType UnOpFun :: UnOpType UnOpPrefix :: UnOpType UnOpPostfix :: UnOpType sqlUnOp :: UnOp -> (String, UnOpType) showAggrOp :: AggrOp -> String defaultSqlLiteral :: SqlGenerator -> Literal -> String defaultSqlQuote :: SqlGenerator -> String -> String -- | Quote a string and escape characters that need escaping We use -- Postgres "escape strings", i.e. strings prefixed with E, to ensure -- that escaping with backslash is valid. quote :: String -> String -- | Escape characters that need escaping escape :: Char -> String -- | Quote binary literals using Postgresql's hex format. binQuote :: ByteString -> String module Opaleye.Internal.Sql data Select SelectFrom :: From -> Select Table :: SqlTable -> Select -- | A relation-valued expression RelExpr :: SqlExpr -> Select SelectJoin :: Join -> Select SelectValues :: Values -> Select SelectBinary :: Binary -> Select SelectLabel :: Label -> Select data SelectAttrs Star :: SelectAttrs SelectAttrs :: (NonEmpty (SqlExpr, Maybe SqlColumn)) -> SelectAttrs data From From :: SelectAttrs -> [Select] -> [SqlExpr] -> Maybe (NonEmpty SqlExpr) -> [(SqlExpr, SqlOrder)] -> Maybe Int -> Maybe Int -> From [attrs] :: From -> SelectAttrs [tables] :: From -> [Select] [criteria] :: From -> [SqlExpr] [groupBy] :: From -> Maybe (NonEmpty SqlExpr) [orderBy] :: From -> [(SqlExpr, SqlOrder)] [limit] :: From -> Maybe Int [offset] :: From -> Maybe Int data Join Join :: JoinType -> (Select, Select) -> SqlExpr -> Join [jJoinType] :: Join -> JoinType [jTables] :: Join -> (Select, Select) [jCond] :: Join -> SqlExpr data Values Values :: SelectAttrs -> [[SqlExpr]] -> Values [vAttrs] :: Values -> SelectAttrs [vValues] :: Values -> [[SqlExpr]] data Binary Binary :: BinOp -> Select -> Select -> Binary [bOp] :: Binary -> BinOp [bSelect1] :: Binary -> Select [bSelect2] :: Binary -> Select data JoinType LeftJoin :: JoinType RightJoin :: JoinType FullJoin :: JoinType data BinOp Except :: BinOp ExceptAll :: BinOp Union :: BinOp UnionAll :: BinOp Intersect :: BinOp IntersectAll :: BinOp data Label Label :: String -> Select -> Label [lLabel] :: Label -> String [lSelect] :: Label -> Select data Returning a Returning :: a -> (NonEmpty SqlExpr) -> Returning a sqlQueryGenerator :: PrimQueryFold' Void Select sql :: ([PrimExpr], PrimQuery' Void, Tag) -> Select unit :: Select empty :: Void -> select baseTable :: TableIdentifier -> [(Symbol, PrimExpr)] -> Select product :: NonEmpty Select -> [PrimExpr] -> Select aggregate :: [(Symbol, (Maybe (AggrOp, [OrderExpr]), PrimExpr))] -> Select -> Select aggrExpr :: Maybe (AggrOp, [OrderExpr]) -> PrimExpr -> PrimExpr order :: [OrderExpr] -> Select -> Select limit_ :: LimitOp -> Select -> Select join :: JoinType -> PrimExpr -> Select -> Select -> Select values :: [Symbol] -> NonEmpty [PrimExpr] -> Select binary :: BinOp -> [(Symbol, (PrimExpr, PrimExpr))] -> (Select, Select) -> Select joinType :: JoinType -> JoinType binOp :: BinOp -> BinOp newSelect :: From sqlExpr :: PrimExpr -> SqlExpr sqlBinding :: (Symbol, PrimExpr) -> (SqlExpr, Maybe SqlColumn) ensureColumns :: [(SqlExpr, Maybe a)] -> NonEmpty (SqlExpr, Maybe a) -- | For ensuring that we have at least one column in a SELECT or RETURNING ensureColumnsGen :: (SqlExpr -> a) -> [a] -> NonEmpty a label :: String -> Select -> Select relExpr :: PrimExpr -> [(Symbol, PrimExpr)] -> Select instance GHC.Show.Show Opaleye.Internal.Sql.From instance GHC.Show.Show Opaleye.Internal.Sql.Join instance GHC.Show.Show Opaleye.Internal.Sql.Binary instance GHC.Show.Show Opaleye.Internal.Sql.Select instance GHC.Show.Show Opaleye.Internal.Sql.Label instance GHC.Show.Show Opaleye.Internal.Sql.BinOp instance GHC.Show.Show Opaleye.Internal.Sql.JoinType instance GHC.Show.Show Opaleye.Internal.Sql.Values instance GHC.Show.Show Opaleye.Internal.Sql.SelectAttrs module Opaleye.Internal.Print type TableAlias = String ppSql :: Select -> Doc ppSelectFrom :: From -> Doc ppSelectJoin :: Join -> Doc ppSelectValues :: Values -> Doc ppSelectBinary :: Binary -> Doc ppSelectLabel :: Label -> Doc ppJoinType :: JoinType -> Doc ppAttrs :: SelectAttrs -> Doc nameAs :: (SqlExpr, Maybe SqlColumn) -> Doc ppTables :: [Select] -> Doc tableAlias :: Int -> Select -> (TableAlias, Select) ppTable :: (TableAlias, Select) -> Doc ppGroupBy :: Maybe (NonEmpty SqlExpr) -> Doc ppLimit :: Maybe Int -> Doc ppOffset :: Maybe Int -> Doc ppValues :: [[SqlExpr]] -> Doc ppValuesRow :: [SqlExpr] -> Doc ppBinOp :: BinOp -> Doc ppInsertReturning :: Returning SqlInsert -> Doc ppUpdateReturning :: Returning SqlUpdate -> Doc module Opaleye.Internal.PackMap -- | 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. data PackMap a b s t PackMap :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> PackMap a b s t -- | 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. traversePM :: Applicative f => PackMap a b s t -> (a -> f b) -> s -> f t -- | 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. overPM :: PackMap a b s t -> (a -> b) -> s -> t -- | A helpful monad for writing columns in the AST type PM a = State (a, Int) new :: PM a String write :: a -> PM [a] () run :: PM [a] r -> (r, [a]) -- | 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. extractAttrPE :: (primExpr -> String -> String) -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr -- | As extractAttrPE but ignores the primExpr when making -- the fresh column name and just uses the supplied String and -- Tag. extractAttr :: String -> Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr eitherFunction :: Functor f => (a -> f b) -> (a' -> f b') -> Either a a' -> f (Either b b') instance GHC.Base.Functor (Opaleye.Internal.PackMap.PackMap a b s) instance GHC.Base.Applicative (Opaleye.Internal.PackMap.PackMap a b s) instance Data.Profunctor.Unsafe.Profunctor (Opaleye.Internal.PackMap.PackMap a b) instance Data.Profunctor.Product.Class.ProductProfunctor (Opaleye.Internal.PackMap.PackMap a b) instance Data.Profunctor.Product.SumProfunctor (Opaleye.Internal.PackMap.PackMap a b) module Opaleye.Internal.Column newtype Column a Column :: PrimExpr -> Column a -- | Only used within a Column, to indicate that it can take null -- values. data Nullable a Nullable :: Nullable a unColumn :: Column a -> PrimExpr -- | Deprecated: Use unsafeCoerceColumn instead unsafeCoerce :: Column a -> Column b -- | Treat a Column as though it were of a different type. If such a -- treatment is not valid then Postgres may fail with an error at SQL run -- time. unsafeCoerceColumn :: Column a -> Column b -- | Cast a column to any other type. Implements Postgres's :: or -- CAST( ... AS ... ) operations. This is safe for some -- conversions, such as uuid to text. unsafeCast :: String -> Column a -> Column b unsafeCompositeField :: Column a -> String -> Column b binOp :: BinOp -> Column a -> Column b -> Column c unOp :: UnOp -> Column a -> Column b unsafeCase_ :: [(Column pgBool, Column a)] -> Column a -> Column a unsafeIfThenElse :: Column pgBool -> Column a -> Column a -> Column a unsafeGt :: Column a -> Column a -> Column pgBool unsafeEq :: Column a -> Column a -> Column pgBool class PGNum a pgFromInteger :: PGNum a => Integer -> Column a class PGFractional a pgFromRational :: PGFractional a => Rational -> Column a -- | A dummy typeclass whose instances support integral operations. class PGIntegral a class PGString a pgFromString :: PGString a => String -> Column a instance GHC.Show.Show (Opaleye.Internal.Column.Column a) instance Opaleye.Internal.Column.PGNum a => GHC.Num.Num (Opaleye.Internal.Column.Column a) instance (Opaleye.Internal.Column.PGNum a, Opaleye.Internal.Column.PGFractional a) => GHC.Real.Fractional (Opaleye.Internal.Column.Column a) instance Opaleye.Internal.Column.PGString a => Data.String.IsString (Opaleye.Internal.Column.Column a) module Opaleye.Internal.PGTypes unsafePgFormatTime :: FormatTime t => Name -> String -> t -> Column c literalColumn :: Literal -> Column a castToType :: Name -> String -> Column c strictDecodeUtf8 :: ByteString -> String lazyDecodeUtf8 :: ByteString -> String -- | Postgres types and functions to create Columns of those types. -- You may find it more convenient to use Opaleye.Constant -- instead. module Opaleye.PGTypes pgString :: String -> Column PGText pgLazyByteString :: ByteString -> Column PGBytea pgStrictByteString :: ByteString -> Column PGBytea pgStrictText :: Text -> Column PGText pgLazyText :: Text -> Column PGText pgInt4 :: Int -> Column PGInt4 pgInt8 :: Int64 -> Column PGInt8 pgDouble :: Double -> Column PGFloat8 pgBool :: Bool -> Column PGBool pgUUID :: UUID -> Column PGUuid pgDay :: Day -> Column PGDate pgUTCTime :: UTCTime -> Column PGTimestamptz pgLocalTime :: LocalTime -> Column PGTimestamp pgTimeOfDay :: TimeOfDay -> Column PGTime pgCiStrictText :: CI Text -> Column PGCitext pgCiLazyText :: CI Text -> Column PGCitext pgJSON :: String -> Column PGJson pgStrictJSON :: ByteString -> Column PGJson pgLazyJSON :: ByteString -> Column PGJson pgValueJSON :: ToJSON a => a -> Column PGJson pgJSONB :: String -> Column PGJsonb pgStrictJSONB :: ByteString -> Column PGJsonb pgLazyJSONB :: ByteString -> Column PGJsonb pgValueJSONB :: ToJSON a => a -> Column PGJsonb pgArray :: forall a b. IsSqlType b => (a -> Column b) -> [a] -> Column (PGArray b) class IsSqlType pgType showPGType :: IsSqlType pgType => proxy pgType -> String data PGBool data PGDate data PGFloat4 data PGFloat8 data PGInt8 data PGInt4 data PGInt2 data PGNumeric data PGText data PGTime data PGTimestamp data PGTimestamptz data PGUuid data PGCitext data PGArray a data PGBytea data PGJson data PGJsonb -- | Warning: literalColumn has been moved to -- Opaleye.Internal.PGTypes and will be deprecated in a future -- release literalColumn :: Literal -> Column a -- | Warning: unsafePgFormatTime has been moved to -- Opaleye.Internal.PGTypes and will be deprecated in a future -- release unsafePgFormatTime :: FormatTime t => Name -> String -> t -> Column c instance Opaleye.Internal.Column.PGNum Opaleye.PGTypes.PGFloat8 instance Opaleye.Internal.Column.PGNum Opaleye.PGTypes.PGInt4 instance Opaleye.Internal.Column.PGNum Opaleye.PGTypes.PGInt8 instance Opaleye.Internal.Column.PGFractional Opaleye.PGTypes.PGFloat8 instance Opaleye.Internal.Column.PGIntegral Opaleye.PGTypes.PGInt2 instance Opaleye.Internal.Column.PGIntegral Opaleye.PGTypes.PGInt4 instance Opaleye.Internal.Column.PGIntegral Opaleye.PGTypes.PGInt8 instance Opaleye.Internal.Column.PGString Opaleye.PGTypes.PGText instance Opaleye.Internal.Column.PGString Opaleye.PGTypes.PGCitext instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGBool instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGDate instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGFloat4 instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGFloat8 instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGInt8 instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGInt4 instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGInt2 instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGNumeric instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGText instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGTime instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGTimestamp instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGTimestamptz instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGUuid instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGCitext instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGBytea instance Opaleye.PGTypes.IsSqlType a => Opaleye.PGTypes.IsSqlType (Opaleye.PGTypes.PGArray a) instance Opaleye.PGTypes.IsSqlType a => Opaleye.PGTypes.IsSqlType (Opaleye.Internal.Column.Nullable a) instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGJson instance Opaleye.PGTypes.IsSqlType Opaleye.PGTypes.PGJsonb -- | Functions for working directly with Columns. -- -- Please note that numeric Column types are instances of -- Num, so you can use *, /, +, - on -- them. module Opaleye.Column -- | A NULL of any type null :: Column (Nullable a) -- | TRUE if the value of the column is NULL, -- FALSE otherwise. isNull :: Column (Nullable a) -> Column PGBool -- | If the Column (Nullable a) is NULL then return the Column -- b otherwise map the underlying Column a using the -- provided function. -- -- The Opaleye equivalent of maybe. matchNullable :: Column b -> (Column a -> Column b) -> Column (Nullable a) -> Column b -- | If the Column (Nullable a) is NULL then return the provided -- Column a otherwise return the underlying Column a. -- -- The Opaleye equivalent of fromMaybe. fromNullable :: Column a -> Column (Nullable a) -> Column a -- | Treat a column as though it were nullable. This is always safe. -- -- The Opaleye equivalent of Just. toNullable :: Column a -> Column (Nullable a) -- | If the argument is Nothing return NULL otherwise return the -- provided value coerced to a nullable type. maybeToNullable :: Maybe (Column a) -> Column (Nullable a) data Column a -- | Only used within a Column, to indicate that it can take null -- values. data Nullable a -- | Cast a column to any other type. Implements Postgres's :: or -- CAST( ... AS ... ) operations. This is safe for some -- conversions, such as uuid to text. unsafeCast :: String -> Column a -> Column b -- | Deprecated: Use unsafeCoerceColumn instead unsafeCoerce :: Column a -> Column b -- | Treat a Column as though it were of a different type. If such a -- treatment is not valid then Postgres may fail with an error at SQL run -- time. unsafeCoerceColumn :: Column a -> Column b unsafeCompositeField :: Column a -> String -> Column b module Opaleye.Constant -- | constant provides a convenient typeclass wrapper around the -- Column creation functions in Opaleye.PGTypes. Besides -- convenience it doesn't provide any additional functionality. -- -- It can be used with functions like runInsert to insert custom -- Haskell types into the database. The following is an example of a -- function for inserting custom types. -- --
--   customInsert
--      :: ( Default Constant haskells columns )
--      => Connection
--      -> Table columns columns'
--      -> haskells
--      -> IO Int64
--   customInsert conn table haskells = runInsert conn table $ constant haskells
--   
-- -- In order to use this function with your custom types, you need to -- define an instance of Default Constant for your custom -- types. constant :: Default Constant haskells columns => haskells -> columns newtype Constant haskells columns Constant :: (haskells -> columns) -> Constant haskells columns [constantExplicit] :: Constant haskells columns -> haskells -> columns instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant haskell (Opaleye.Internal.Column.Column sql) => Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant (GHC.Base.Maybe haskell) (Opaleye.Internal.Column.Column (Opaleye.Internal.Column.Nullable sql)) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Base.String (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGText) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Lazy.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGBytea) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGBytea) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Text.Internal.Text (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGText) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Text.Internal.Lazy.Text (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGText) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Types.Int (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGInt4) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Int.Int32 (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGInt4) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Int.Int64 (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGInt8) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Types.Double (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGFloat8) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant GHC.Types.Bool (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGBool) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.UUID.Types.Internal.UUID (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGUuid) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Time.Calendar.Days.Day (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGDate) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Time.Clock.UTC.UTCTime (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGTimestamptz) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Time.LocalTime.LocalTime.LocalTime (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGTimestamp) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Time.LocalTime.TimeOfDay.TimeOfDay (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGTime) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant (Data.CaseInsensitive.Internal.CI Data.Text.Internal.Text) (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGCitext) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant (Data.CaseInsensitive.Internal.CI Data.Text.Internal.Lazy.Text) (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGCitext) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJson) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Lazy.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJson) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Aeson.Types.Internal.Value (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJson) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJsonb) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.ByteString.Lazy.Internal.ByteString (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJsonb) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant Data.Aeson.Types.Internal.Value (Opaleye.Internal.Column.Column Opaleye.PGTypes.PGJsonb) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant haskell (Opaleye.Internal.Column.Column sql) => Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant (GHC.Base.Maybe haskell) (GHC.Base.Maybe (Opaleye.Internal.Column.Column sql)) instance (Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant a (Opaleye.Internal.Column.Column b), Opaleye.PGTypes.IsSqlType b) => Data.Profunctor.Product.Default.Class.Default Opaleye.Constant.Constant [a] (Opaleye.Internal.Column.Column (Opaleye.PGTypes.PGArray b)) instance GHC.Base.Functor (Opaleye.Constant.Constant a) instance GHC.Base.Applicative (Opaleye.Constant.Constant a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Constant.Constant instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Constant.Constant instance Data.Profunctor.Product.SumProfunctor Opaleye.Constant.Constant module Opaleye.Internal.Unpackspec newtype Unpackspec columns columns' -- | An Unpackspec columns columns' allows you to -- extract and modify a sequence of PrimExprs inside a value of -- type columns. -- -- For example, the Default instance of type Unpackspec -- (Column a, Column b) (Column a, Column b) allows you -- to manipulate or extract the two PrimExprs inside a (Column -- a, Column b). The Default instance of type Foo -- (Column a) (Column b) (Column c) will allow you to manipulate or -- extract the three PrimExprs contained therein (for a -- user-defined product type Foo, assuming the -- makeAdaptorAndInstance splice from -- Data.Profunctor.Product.TH has been run). -- -- You can create Unpackspecs by hand using -- unpackspecColumn and the Profunctor, -- ProductProfunctor and SumProfunctor operations. -- However, in practice users should almost never need to create or -- manipulate them. Typically they will be created automatically by the -- Default instance. Unpackspec :: (PackMap PrimExpr PrimExpr columns columns') -> Unpackspec columns columns' -- | Target the single PrimExpr inside a Column unpackspecColumn :: Unpackspec (Column a) (Column a) -- | Modify all the targeted PrimExprs runUnpackspec :: Applicative f => Unpackspec columns b -> (PrimExpr -> f PrimExpr) -> columns -> f b -- | Extract all the targeted PrimExprs collectPEs :: Unpackspec s t -> s -> [PrimExpr] instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Unpackspec.Unpackspec (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance GHC.Base.Functor (Opaleye.Internal.Unpackspec.Unpackspec a) instance GHC.Base.Applicative (Opaleye.Internal.Unpackspec.Unpackspec a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Unpackspec.Unpackspec instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Unpackspec.Unpackspec instance Data.Profunctor.Product.SumProfunctor Opaleye.Internal.Unpackspec.Unpackspec module Opaleye.Internal.QueryArr -- | QueryArr a b is analogous to a Haskell function a -> -- [b]. newtype QueryArr a b QueryArr :: ((a, PrimQuery, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b -- | A Postgres query, i.e. some functionality that can run via SQL and -- produce a collection of rows. -- -- Query a is analogous to a Haskell value [a]. type Query = QueryArr () simpleQueryArr :: ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b runQueryArr :: QueryArr a b -> (a, PrimQuery, Tag) -> (b, 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) instance Control.Category.Category Opaleye.Internal.QueryArr.QueryArr instance Control.Arrow.Arrow Opaleye.Internal.QueryArr.QueryArr instance GHC.Base.Functor (Opaleye.Internal.QueryArr.QueryArr a) instance GHC.Base.Applicative (Opaleye.Internal.QueryArr.QueryArr a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.QueryArr.QueryArr instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.QueryArr.QueryArr -- | Query and QueryArr are the composable units of database -- querying that are used in Opaleye. module Opaleye.QueryArr -- | A Postgres query, i.e. some functionality that can run via SQL and -- produce a collection of rows. -- -- Query a is analogous to a Haskell value [a]. type Query = QueryArr () -- | QueryArr a b is analogous to a Haskell function a -> -- [b]. data QueryArr a b module Opaleye.Label -- | Add a commented label to the generated SQL. label :: String -> Query a -> Query a module Opaleye.Sql -- | When Nothing is returned it means that the Query -- returns zero rows. -- -- Example type specialization: -- --
--   showSqlForPostgres :: Query (Column a, Column b) -> Maybe String
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   showSqlForPostgres :: Query (Foo (Column a) (Column b) (Column c)) -> Maybe String
--   
showSqlForPostgres :: forall columns. Default Unpackspec columns columns => Query columns -> Maybe String showSqlForPostgresUnopt :: forall columns. Default Unpackspec columns columns => Query columns -> Maybe String showSqlForPostgresExplicit :: Unpackspec columns b -> Query columns -> Maybe String showSqlForPostgresUnoptExplicit :: Unpackspec columns b -> Query columns -> Maybe String -- | For internal use only. Do not use. Will be deprecated in a future -- release. formatAndShowSQL :: ([PrimExpr], PrimQuery' a, Tag) -> Maybe String module Opaleye.Internal.Binary extractBinaryFields :: Tag -> (PrimExpr, PrimExpr) -> PM [(Symbol, (PrimExpr, PrimExpr))] PrimExpr newtype Binaryspec columns columns' Binaryspec :: (PackMap (PrimExpr, PrimExpr) PrimExpr (columns, columns) columns') -> Binaryspec columns columns' runBinaryspec :: Applicative f => Binaryspec columns columns' -> ((PrimExpr, PrimExpr) -> f PrimExpr) -> (columns, columns) -> f columns' binaryspecColumn :: Binaryspec (Column a) (Column a) sameTypeBinOpHelper :: BinOp -> Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Binary.Binaryspec (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance GHC.Base.Functor (Opaleye.Internal.Binary.Binaryspec a) instance GHC.Base.Applicative (Opaleye.Internal.Binary.Binaryspec a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Binary.Binaryspec instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Binary.Binaryspec module Opaleye.Internal.Values valuesU :: Unpackspec columns columns' -> Valuesspec columns columns' -> [columns] -> ((), Tag) -> (columns', PrimQuery, Tag) extractValuesEntry :: PrimExpr -> PM [PrimExpr] PrimExpr extractValuesField :: Tag -> primExpr -> PM [(Symbol, primExpr)] PrimExpr newtype Valuesspec columns columns' Valuesspec :: (PackMap () PrimExpr () columns') -> Valuesspec columns columns' runValuesspec :: Applicative f => Valuesspec columns columns' -> (() -> f PrimExpr) -> f columns' instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Values.Valuesspec (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance GHC.Base.Functor (Opaleye.Internal.Values.Valuesspec a) instance GHC.Base.Applicative (Opaleye.Internal.Values.Valuesspec a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Values.Valuesspec instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Values.Valuesspec module Opaleye.Values -- | values implements Postgres's VALUES construct and -- allows you to create a query that consists of the given rows. -- -- Example type specialization: -- --
--   values :: [(Column a, Column b)] -> Query (Column a, Column b)
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   queryTable :: [Foo (Column a) (Column b) (Column c)] -> Query (Foo (Column a) (Column b) (Column c))
--   
values :: (Default Valuesspec columns columns, Default Unpackspec columns columns) => [columns] -> Query columns valuesExplicit :: Unpackspec columns columns' -> Valuesspec columns columns' -> [columns] -> Query columns' module Opaleye.Internal.Join newtype NullMaker a b NullMaker :: (a -> b) -> NullMaker a b toNullable :: NullMaker a b -> a -> b joinExplicit :: (columnsA -> returnedColumnsA) -> (columnsB -> returnedColumnsB) -> JoinType -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (returnedColumnsA, returnedColumnsB) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Join.NullMaker (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column (Opaleye.Internal.Column.Nullable a)) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Join.NullMaker (Opaleye.Internal.Column.Column (Opaleye.Internal.Column.Nullable a)) (Opaleye.Internal.Column.Column (Opaleye.Internal.Column.Nullable a)) instance GHC.Base.Functor (Opaleye.Internal.Join.NullMaker a) instance GHC.Base.Applicative (Opaleye.Internal.Join.NullMaker a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Join.NullMaker instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Join.NullMaker -- | Left, right, and full outer joins. If you want inner joins, just use -- restrict instead. -- -- The use of the Default typeclass means that the compiler will -- have trouble inferring types. It is strongly recommended that you -- provide full type signatures when using the join functions. -- -- Example specialization: -- --
--   leftJoin :: Query (Column a, Column b)
--            -> Query (Column c, Column (Nullable d))
--            -> (((Column a, Column b), (Column c, Column (Nullable d))) -> Column PGBool)
--            -> Query ((Column a, Column b), (Column (Nullable c), Column (Nullable d)))
--   
module Opaleye.Join leftJoin :: (Default Unpackspec columnsA columnsA, Default Unpackspec columnsB columnsB, Default NullMaker columnsB nullableColumnsB) => Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (columnsA, nullableColumnsB) rightJoin :: (Default Unpackspec columnsA columnsA, Default Unpackspec columnsB columnsB, Default NullMaker columnsA nullableColumnsA) => Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (nullableColumnsA, columnsB) fullJoin :: (Default Unpackspec columnsA columnsA, Default Unpackspec columnsB columnsB, Default NullMaker columnsA nullableColumnsA, Default NullMaker columnsB nullableColumnsB) => Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (nullableColumnsA, nullableColumnsB) leftJoinExplicit :: Unpackspec columnsA columnsA -> Unpackspec columnsB columnsB -> NullMaker columnsB nullableColumnsB -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (columnsA, nullableColumnsB) rightJoinExplicit :: Unpackspec columnsA columnsA -> Unpackspec columnsB columnsB -> NullMaker columnsA nullableColumnsA -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (nullableColumnsA, columnsB) fullJoinExplicit :: Unpackspec columnsA columnsA -> Unpackspec columnsB columnsB -> NullMaker columnsA nullableColumnsA -> NullMaker columnsB nullableColumnsB -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (nullableColumnsA, nullableColumnsB) module Opaleye.Internal.RunQuery -- | A QueryRunnerColumn pgType haskellType -- encodes how to turn a value of Postgres type pgType into a -- value of Haskell type haskellType. For example a value of -- type QueryRunnerColumn PGText String encodes how -- to turn a PGText result from the database into a Haskell -- String. data QueryRunnerColumn pgType haskellType QueryRunnerColumn :: (Unpackspec (Column pgType) ()) -> (FieldParser haskellType) -> QueryRunnerColumn pgType haskellType data QueryRunner columns haskells -- | Have we actually requested any columns? If we asked for zero columns -- then the SQL generator will have to put a dummy 0 into the SELECT -- statement, since we can't select zero columns. In that case we have to -- make sure we read a single Int. QueryRunner :: (Unpackspec columns ()) -> (columns -> RowParser haskells) -> (columns -> Bool) -> QueryRunner columns haskells fieldQueryRunnerColumn :: FromField haskell => QueryRunnerColumn pgType haskell fieldParserQueryRunnerColumn :: FieldParser haskell -> QueryRunnerColumn pgType haskell queryRunner :: QueryRunnerColumn a b -> QueryRunner (Column a) b queryRunnerColumnNullable :: QueryRunnerColumn a b -> QueryRunnerColumn (Nullable a) (Maybe b) -- | A QueryRunnerColumnDefault pgType haskellType -- represents the default way to turn a pgType result from the -- database into a Haskell value of type haskellType. -- -- Creating an instance of QueryRunnerColumnDefault for your own -- types is necessary for retrieving those types from the database. -- -- You should use one of the three methods below for writing a -- QueryRunnerColumnDefault instance. -- --
    --
  1. If you already have a FromField instance for your -- haskellType, use fieldQueryRunnerColumn. (This is how -- most of the built-in instances are defined.)
  2. --
  3. If you don't have a FromField instance, use -- queryRunnerColumn if possible. See the documentation for -- queryRunnerColumn for an example.
  4. --
  5. If you have a more complicated case, but not a FromField -- instance, write a FieldParser for your type and use -- fieldParserQueryRunnerColumn. You can also add a -- FromField instance using this.
  6. --
class QueryRunnerColumnDefault pgType haskellType queryRunnerColumnDefault :: QueryRunnerColumnDefault pgType haskellType => QueryRunnerColumn pgType haskellType arrayColumn :: Column (PGArray a) -> Column a arrayFieldParser :: Typeable a => FieldParser a -> FieldParser (PGArray a) fromArray :: FieldParser a -> TypeInfo -> Field -> Parser (Conversion [a]) jsonFieldParser :: FieldParser String jsonbFieldParser :: FieldParser String jsonFieldTypeParser :: ByteString -> FieldParser String prepareRowParser :: QueryRunner columns haskells -> columns -> RowParser haskells instance GHC.Base.Functor (Opaleye.Internal.RunQuery.QueryRunnerColumn u) instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault a b => Opaleye.Internal.RunQuery.QueryRunnerColumnDefault (Opaleye.Internal.Column.Nullable a) (GHC.Base.Maybe b) instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault a b => Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.RunQuery.QueryRunner (Opaleye.Internal.Column.Column a) b instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGInt4 GHC.Types.Int instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGInt4 GHC.Int.Int32 instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGInt8 GHC.Int.Int64 instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGText GHC.Base.String instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGFloat8 GHC.Types.Double instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGBool GHC.Types.Bool instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGUuid Data.UUID.Types.Internal.UUID instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGBytea Data.ByteString.Internal.ByteString instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGBytea Data.ByteString.Lazy.Internal.ByteString instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGText Data.Text.Internal.Text instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGText Data.Text.Internal.Lazy.Text instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGDate Data.Time.Calendar.Days.Day instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGTimestamptz Data.Time.Clock.UTC.UTCTime instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGTimestamp Data.Time.LocalTime.LocalTime.LocalTime instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGTime Data.Time.LocalTime.TimeOfDay.TimeOfDay instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGCitext (Data.CaseInsensitive.Internal.CI Data.Text.Internal.Text) instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGCitext (Data.CaseInsensitive.Internal.CI Data.Text.Internal.Lazy.Text) instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGJson GHC.Base.String instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGJson Data.Aeson.Types.Internal.Value instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGJsonb GHC.Base.String instance Opaleye.Internal.RunQuery.QueryRunnerColumnDefault Opaleye.PGTypes.PGJsonb Data.Aeson.Types.Internal.Value instance (Data.Typeable.Internal.Typeable b, Opaleye.Internal.RunQuery.QueryRunnerColumnDefault a b) => Opaleye.Internal.RunQuery.QueryRunnerColumnDefault (Opaleye.PGTypes.PGArray a) [b] instance GHC.Base.Functor (Opaleye.Internal.RunQuery.QueryRunner c) instance GHC.Base.Applicative (Opaleye.Internal.RunQuery.QueryRunner c) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.RunQuery.QueryRunner instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.RunQuery.QueryRunner instance Data.Profunctor.Product.SumProfunctor Opaleye.Internal.RunQuery.QueryRunner module Opaleye.RunQuery -- | runQuery's use of the Default typeclass means that the -- compiler will have trouble inferring types. It is strongly recommended -- that you provide full type signatures when using runQuery. -- -- Example type specialization: -- --
--   runQuery :: Query (Column PGInt4, Column PGText) -> IO [(Column Int, Column String)]
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   runQuery :: Query (Foo (Column PGInt4) (Column PGText) (Column PGBool)
--            -> IO [(Foo (Column Int) (Column String) (Column Bool)]
--   
-- -- Opaleye types are converted to Haskell types based on instances of the -- QueryRunnerColumnDefault typeclass. runQuery :: Default QueryRunner columns haskells => Connection -> Query columns -> IO [haskells] -- | runQueryFold streams the results of a query incrementally and -- consumes the results with a left fold. -- -- This fold is not strict. The stream consumer is responsible for -- forcing the evaluation of its result to avoid space leaks. runQueryFold :: Default QueryRunner columns haskells => Connection -> Query columns -> b -> (b -> haskells -> IO b) -> IO b -- | Use queryRunnerColumn to make an instance to allow you to run -- queries on your own datatypes. For example: -- --
--   newtype Foo = Foo Int
--   
--   instance QueryRunnerColumnDefault Foo Foo where
--      queryRunnerColumnDefault =
--          queryRunnerColumn (unsafeCoerceColumn
--                                 :: Column Foo -> Column PGInt4)
--                            Foo
--                            queryRunnerColumnDefault
--   
queryRunnerColumn :: (Column a' -> Column a) -> (b -> b') -> QueryRunnerColumn a b -> QueryRunnerColumn a' b' runQueryExplicit :: QueryRunner columns haskells -> Connection -> Query columns -> IO [haskells] runQueryFoldExplicit :: QueryRunner columns haskells -> Connection -> Query columns -> b -> (b -> haskells -> IO b) -> IO b -- | For internal use only. Do not use. Will be deprecated in a subsequent -- release. prepareQuery :: QueryRunner columns haskells -> Query columns -> (Maybe Query, RowParser haskells) data QueryRunner columns haskells -- | A QueryRunnerColumn pgType haskellType -- encodes how to turn a value of Postgres type pgType into a -- value of Haskell type haskellType. For example a value of -- type QueryRunnerColumn PGText String encodes how -- to turn a PGText result from the database into a Haskell -- String. data QueryRunnerColumn pgType haskellType -- | A QueryRunnerColumnDefault pgType haskellType -- represents the default way to turn a pgType result from the -- database into a Haskell value of type haskellType. -- -- Creating an instance of QueryRunnerColumnDefault for your own -- types is necessary for retrieving those types from the database. -- -- You should use one of the three methods below for writing a -- QueryRunnerColumnDefault instance. -- --
    --
  1. If you already have a FromField instance for your -- haskellType, use fieldQueryRunnerColumn. (This is how -- most of the built-in instances are defined.)
  2. --
  3. If you don't have a FromField instance, use -- queryRunnerColumn if possible. See the documentation for -- queryRunnerColumn for an example.
  4. --
  5. If you have a more complicated case, but not a FromField -- instance, write a FieldParser for your type and use -- fieldParserQueryRunnerColumn. You can also add a -- FromField instance using this.
  6. --
class QueryRunnerColumnDefault pgType haskellType queryRunnerColumnDefault :: QueryRunnerColumnDefault pgType haskellType => QueryRunnerColumn pgType haskellType fieldQueryRunnerColumn :: FromField haskell => QueryRunnerColumn pgType haskell fieldParserQueryRunnerColumn :: FieldParser haskell -> QueryRunnerColumn pgType haskell module Opaleye.Internal.Order -- | An Order represents an expression to order on and a sort -- direction. Multiple Orders can be composed with mappend -- or (<>) from Data.Monoid. If two rows are equal -- according to the first Order, the second is used, and so on. newtype Order a Order :: (a -> [(OrderOp, PrimExpr)]) -> Order a order :: OrderOp -> (a -> Column b) -> Order a orderByU :: Order a -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag) orderExprs :: a -> Order a -> [OrderExpr] limit' :: Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag) offset' :: Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag) instance Data.Functor.Contravariant.Contravariant Opaleye.Internal.Order.Order instance Data.Semigroup.Semigroup (Opaleye.Internal.Order.Order a) instance GHC.Base.Monoid (Opaleye.Internal.Order.Order a) instance Data.Functor.Contravariant.Divisible.Divisible Opaleye.Internal.Order.Order instance Data.Functor.Contravariant.Divisible.Decidable Opaleye.Internal.Order.Order -- | Ordering, LIMIT and OFFSET module Opaleye.Order -- | Order the rows of a Query according to the Order. -- --
--   import Data.Monoid (<>)
--   
--   -- Order by the first column ascending.  When first columns are equal
--   -- order by second column descending.
--   example :: Query (Column PGInt4, Column PGText)
--           -> Query (Column PGInt4, Column PGText)
--   example = orderBy (asc fst <> desc snd)
--   
orderBy :: Order a -> Query a -> Query a -- | Specify an ascending ordering by the given expression. (Any NULLs -- appear last) asc :: PGOrd b => (a -> Column b) -> Order a -- | Specify an descending ordering by the given expression. (Any NULLs -- appear first) desc :: PGOrd b => (a -> Column b) -> Order a -- | Specify an ascending ordering by the given expression. (Any NULLs -- appear first) ascNullsFirst :: PGOrd b => (a -> Column b) -> Order a -- | Specify an descending ordering by the given expression. (Any NULLs -- appear last) descNullsLast :: PGOrd b => (a -> Column b) -> Order a -- | Limit the results of the given query to the given maximum number of -- items. limit :: Int -> Query a -> Query a -- | Offset the results of the given query by the given amount, skipping -- that many result rows. offset :: Int -> Query a -> Query a -- | Typeclass for Postgres types which support ordering operations. class PGOrd a -- | An Order represents an expression to order on and a sort -- direction. Multiple Orders can be composed with mappend -- or (<>) from Data.Monoid. If two rows are equal -- according to the first Order, the second is used, and so on. data Order a instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGBool instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGDate instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGFloat8 instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGFloat4 instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGInt8 instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGInt4 instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGInt2 instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGNumeric instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGText instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGTime instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGTimestamptz instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGTimestamp instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGCitext instance Opaleye.Order.PGOrd Opaleye.PGTypes.PGUuid instance Opaleye.Order.PGOrd a => Opaleye.Order.PGOrd (Opaleye.Internal.Column.Nullable a) module Opaleye.Internal.Aggregate -- | An Aggregator takes a collection of rows of type a, -- groups them, and transforms each group into a single row of type -- b. This corresponds to aggregators using GROUP BY in -- SQL. -- -- An Aggregator corresponds closely to a Fold from the -- foldl package. Whereas an Aggregator a -- b takes each group of type a to a single row of type -- b, a Fold a b takes a list of -- a and returns a single row of type b. newtype Aggregator a b Aggregator :: (PackMap (Maybe (AggrOp, [OrderExpr]), PrimExpr) PrimExpr a b) -> Aggregator a b makeAggr' :: Maybe AggrOp -> Aggregator (Column a) (Column b) makeAggr :: AggrOp -> Aggregator (Column a) (Column b) -- | Order the values within each aggregation in Aggregator using -- the given ordering. This is only relevant for aggregations that depend -- on the order they get their elements, like arrayAgg and -- stringAgg. -- -- You can either apply it to an aggregation of multiple columns, in -- which case it will apply to all aggregation functions in there, or you -- can apply it to a single column, and then compose the aggregations -- afterwards. Examples: -- --
--   x :: Aggregator (Column a, Column b) (Column (PGArray a), Column (PGArray a))
--   x = (,) <$> orderAggregate (asc snd) (lmap fst arrayAggGrouped)
--           <*> orderAggregate (desc snd) (lmap fst arrayAggGrouped)
--   
-- -- This will generate: -- --
--   SELECT array_agg(a ORDER BY b ASC), array_agg(a ORDER BY b DESC)
--   FROM (SELECT a, b FROM ...)
--   
-- -- Or: -- --
--   x :: Aggregator (Column a, Column b) (Column (PGArray a), Column (PGArray b))
--   x = orderAggregate (asc snd) $ p2 (arrayAggGrouped, arrayAggGrouped)
--   
-- -- This will generate: -- --
--   SELECT array_agg(a ORDER BY b ASC), array_agg(b ORDER BY b ASC)
--   FROM (SELECT a, b FROM ...)
--   
orderAggregate :: Order a -> Aggregator a b -> Aggregator a b runAggregator :: Applicative f => Aggregator a b -> ((Maybe (AggrOp, [OrderExpr]), PrimExpr) -> f PrimExpr) -> a -> f b aggregateU :: Aggregator a b -> (a, PrimQuery, Tag) -> (b, PrimQuery, Tag) extractAggregateFields :: Tag -> (Maybe (AggrOp, [OrderExpr]), PrimExpr) -> PM [(Symbol, (Maybe (AggrOp, [OrderExpr]), PrimExpr))] PrimExpr instance GHC.Base.Functor (Opaleye.Internal.Aggregate.Aggregator a) instance GHC.Base.Applicative (Opaleye.Internal.Aggregate.Aggregator a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Aggregate.Aggregator instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Aggregate.Aggregator instance Data.Profunctor.Product.SumProfunctor Opaleye.Internal.Aggregate.Aggregator module Opaleye.Internal.TableMaker newtype ViewColumnMaker strings columns ViewColumnMaker :: (PackMap () () strings columns) -> ViewColumnMaker strings columns newtype ColumnMaker columns columns' ColumnMaker :: (PackMap PrimExpr PrimExpr columns columns') -> ColumnMaker columns columns' runViewColumnMaker :: ViewColumnMaker strings tablecolumns -> strings -> tablecolumns runColumnMaker :: Applicative f => ColumnMaker tablecolumns columns -> (PrimExpr -> f PrimExpr) -> tablecolumns -> f columns tableColumn :: ViewColumnMaker String (Column a) column :: ColumnMaker (Column a) (Column a) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.TableMaker.ViewColumnMaker GHC.Base.String (Opaleye.Internal.Column.Column a) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.TableMaker.ColumnMaker (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance GHC.Base.Functor (Opaleye.Internal.TableMaker.ViewColumnMaker a) instance GHC.Base.Applicative (Opaleye.Internal.TableMaker.ViewColumnMaker a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.TableMaker.ViewColumnMaker instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.TableMaker.ViewColumnMaker instance GHC.Base.Functor (Opaleye.Internal.TableMaker.ColumnMaker a) instance GHC.Base.Applicative (Opaleye.Internal.TableMaker.ColumnMaker a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.TableMaker.ColumnMaker instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.TableMaker.ColumnMaker module Opaleye.Internal.Table data Table writerColumns viewColumns -- | Uses the default schema name ("public"). Table :: String -> (TableProperties writerColumns viewColumns) -> Table writerColumns viewColumns -- | Schema name ("public" by default in PostgreSQL), table name, -- table properties. TableWithSchema :: String -> String -> (TableProperties writerColumns viewColumns) -> Table writerColumns viewColumns tableIdentifier :: Table writerColumns viewColumns -> TableIdentifier tableProperties :: Table writerColumns viewColumns -> TableProperties writerColumns viewColumns data TableProperties writerColumns viewColumns TableProperties :: Writer writerColumns viewColumns -> View viewColumns -> TableProperties writerColumns viewColumns [tablePropertiesWriter] :: TableProperties writerColumns viewColumns -> Writer writerColumns viewColumns [tablePropertiesView] :: TableProperties writerColumns viewColumns -> View viewColumns data View columns View :: columns -> View columns newtype Writer columns dummy Writer :: (forall f. Functor f => PackMap (f PrimExpr, String) () (f columns) ()) -> Writer columns dummy queryTable :: ColumnMaker viewColumns columns -> Table writerColumns viewColumns -> Tag -> (columns, PrimQuery) runColumnMaker :: ColumnMaker tablecolumns columns -> Tag -> tablecolumns -> (columns, [(Symbol, PrimExpr)]) runWriter :: Writer columns columns' -> columns -> [(PrimExpr, String)] runWriter' :: Writer columns columns' -> NonEmpty columns -> (NonEmpty [PrimExpr], [String]) data Zip a Zip :: NonEmpty [a] -> Zip a [unZip] :: Zip a -> NonEmpty [a] required :: String -> Writer (Column a) (Column a) optional :: String -> Writer (Maybe (Column a)) (Column a) instance GHC.Base.Monoid (Opaleye.Internal.Table.Zip a) instance GHC.Base.Functor (Opaleye.Internal.Table.Writer a) instance GHC.Base.Applicative (Opaleye.Internal.Table.Writer a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Table.Writer instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Table.Writer instance GHC.Base.Functor (Opaleye.Internal.Table.TableProperties a) instance GHC.Base.Applicative (Opaleye.Internal.Table.TableProperties a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Table.TableProperties instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Table.TableProperties instance GHC.Base.Functor (Opaleye.Internal.Table.Table a) module Opaleye.Table -- | Example type specialization: -- --
--   queryTable :: Table w (Column a, Column b) -> Query (Column a, Column b)
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   queryTable :: Table w (Foo (Column a) (Column b) (Column c)) -> Query (Foo (Column a) (Column b) (Column c))
--   
queryTable :: Default ColumnMaker columns columns => Table a columns -> Query columns queryTableExplicit :: ColumnMaker tablecolumns columns -> Table a tablecolumns -> Query columns required :: String -> TableProperties (Column a) (Column a) optional :: String -> TableProperties (Maybe (Column a)) (Column a) data View columns data Writer columns dummy data Table writerColumns viewColumns -- | Uses the default schema name ("public"). Table :: String -> (TableProperties writerColumns viewColumns) -> Table writerColumns viewColumns -- | Schema name ("public" by default in PostgreSQL), table name, -- table properties. TableWithSchema :: String -> String -> (TableProperties writerColumns viewColumns) -> Table writerColumns viewColumns data TableProperties writerColumns viewColumns -- | Inserts, updates and deletes -- -- Please note that you currently you can only INSERT or UPDATE with -- constant values, not the result of SELECTS. That is, you can generate -- SQL of the form -- --
--   INSERT INTO thetable (John, 1);
--   
-- -- but not -- --
--   INSERT INTO thetable
--      SELECT John,
--      (SELECT num FROM thetable ORDER BY num DESC LIMIT 1) + 1;
--   
module Opaleye.Manipulation -- | Insert rows into a table runInsertMany :: Connection -> Table columns columns' -> [columns] -> IO Int64 -- | Insert rows into a table and return a function of the inserted rows -- -- runInsertManyReturning's use of the Default typeclass -- means that the compiler will have trouble inferring types. It is -- strongly recommended that you provide full type signatures when using -- runInsertManyReturning. runInsertManyReturning :: (Default QueryRunner returned haskells) => Connection -> Table columnsW columnsR -> [columnsW] -> (columnsR -> returned) -> IO [haskells] -- | Update rows in a table runUpdate :: Connection -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> IO Int64 -- | Update rows in a table and return a function of the updated rows -- -- runUpdateReturning's use of the Default typeclass -- means that the compiler will have trouble inferring types. It is -- strongly recommended that you provide full type signatures when using -- runInsertReturning. runUpdateReturning :: (Default QueryRunner returned haskells) => Connection -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> (columnsR -> returned) -> IO [haskells] -- | Delete rows from a table runDelete :: Connection -> Table a columnsR -> (columnsR -> Column PGBool) -> IO Int64 -- | You probably don't need this, but can just use -- runInsertReturning instead. You only need it if you want to run -- an INSERT RETURNING statement but need to be explicit about the -- QueryRunner. runInsertReturningExplicit :: QueryRunner returned haskells -> Connection -> Table columnsW columnsR -> columnsW -> (columnsR -> returned) -> IO [haskells] -- | You probably don't need this, but can just use -- runInsertManyReturning instead. You only need it if you want to -- run an UPDATE RETURNING statement but need to be explicit about the -- QueryRunner. runInsertManyReturningExplicit :: QueryRunner returned haskells -> Connection -> Table columnsW columnsR -> [columnsW] -> (columnsR -> returned) -> IO [haskells] -- | You probably don't need this, but can just use -- runUpdateReturning instead. You only need it if you want to run -- an UPDATE RETURNING statement but need to be explicit about the -- QueryRunner. runUpdateReturningExplicit :: QueryRunner returned haskells -> Connection -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> (columnsR -> returned) -> IO [haskells] -- | Returns the number of rows inserted -- -- This will be deprecated in a future release. Use runInsertMany -- instead. runInsert :: Connection -> Table columns columns' -> columns -> IO Int64 -- | runInsertReturning's use of the Default typeclass -- means that the compiler will have trouble inferring types. It is -- strongly recommended that you provide full type signatures when using -- runInsertReturning. -- -- This will be deprecated in a future release. Use -- runInsertManyReturning instead. runInsertReturning :: (Default QueryRunner returned haskells) => Connection -> Table columnsW columnsR -> columnsW -> (columnsR -> returned) -> IO [haskells] -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsert :: Table columns a -> columns -> SqlInsert -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsertSql :: Table columns a -> columns -> String -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsertMany :: Table columns a -> NonEmpty columns -> SqlInsert -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsertManySql :: Table columns a -> NonEmpty columns -> String -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeUpdate :: Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> SqlUpdate -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeUpdateSql :: Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> String -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeDelete :: Table a columnsR -> (columnsR -> Column PGBool) -> SqlDelete -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeDeleteSql :: Table a columnsR -> (columnsR -> Column PGBool) -> String -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsertManyReturning :: Unpackspec returned ignored -> Table columnsW columnsR -> NonEmpty columnsW -> (columnsR -> returned) -> Returning SqlInsert -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeInsertManyReturningSql :: Unpackspec returned ignored -> Table columnsW columnsR -> NonEmpty columnsW -> (columnsR -> returned) -> String -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeUpdateReturning :: Unpackspec returned ignored -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> (columnsR -> returned) -> Returning SqlUpdate -- | For internal use only. Do not use. Will be removed in a subsequent -- release. arrangeUpdateReturningSql :: Unpackspec returned ignored -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column PGBool) -> (columnsR -> returned) -> String data Unpackspec columns columns' module Opaleye.Internal.Operators (.==) :: forall columns. Default EqPP columns columns => columns -> columns -> Column PGBool infix 4 .== -- | Boolean and (.&&) :: Column PGBool -> Column PGBool -> Column PGBool infixr 3 .&& data EqPP a b EqPP :: (a -> a -> Column PGBool) -> EqPP a b eqExplicit :: EqPP columns a -> columns -> columns -> Column PGBool data RelExprMaker a b RelExprMaker :: ViewColumnMaker a c -> ColumnMaker c b -> RelExprMaker a b [relExprVCM] :: RelExprMaker a b -> ViewColumnMaker a c [relExprCM] :: RelExprMaker a b -> ColumnMaker c b relExprColumn :: RelExprMaker String (Column a) runRelExprMaker :: RelExprMaker strings columns -> Tag -> strings -> (columns, [(Symbol, PrimExpr)]) relationValuedExprExplicit :: RelExprMaker strings columns -> strings -> (a -> PrimExpr) -> QueryArr a columns relationValuedExpr :: Default RelExprMaker strings columns => strings -> (a -> PrimExpr) -> QueryArr a columns instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Operators.EqPP (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Operators.RelExprMaker GHC.Base.String (Opaleye.Internal.Column.Column a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Operators.EqPP instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Operators.EqPP instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Operators.RelExprMaker instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Operators.RelExprMaker -- | Binary relational operations on Querys, that is, operations -- which take two Querys as arguments and return a single -- Query. -- -- All the binary relational operations have the same type -- specializations. For example: -- --
--   unionAll :: Query (Column a, Column b)
--            -> Query (Column a, Column b)
--            -> Query (Column a, Column b)
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   unionAll :: Query (Foo (Column a) (Column b) (Column c))
--            -> Query (Foo (Column a) (Column b) (Column c))
--            -> Query (Foo (Column a) (Column b) (Column c))
--   
-- -- Please note that by design there are no binary relational functions of -- type QueryArr a b -> QueryArr a b -> QueryArr a b. Such -- functions would allow violation of SQL's scoping rules and lead to -- invalid queries. -- -- unionAll is very close to being the | operator -- of a Control.Applicative.Alternative instance but it fails to -- work only because of the typeclass constraint it has. module Opaleye.Binary unionAll :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns -- | The same as unionAll, except that it additionally removes any -- duplicate rows. union :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns intersectAll :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns -- | The same as intersectAll, except that it additionally removes any -- duplicate rows. intersect :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns exceptAll :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns -- | The same as exceptAll, except that it additionally removes any -- duplicate rows. except :: Default Binaryspec columns columns => Query columns -> Query columns -> Query columns unionAllExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' unionExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' intersectAllExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' intersectExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' exceptAllExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' exceptExplicit :: Binaryspec columns columns' -> Query columns -> Query columns -> Query columns' -- | Perform aggregation on Querys. To aggregate a Query you -- should construct an Aggregator encoding how you want the -- aggregation to proceed, then call aggregate on it. module Opaleye.Aggregate -- | Given a Query producing rows of type a and an -- Aggregator accepting rows of type a, apply the -- aggregator to the results of the query. -- -- If you simply want to count the number of rows in a query you might -- find the countRows function more convenient. -- -- By design there is no aggregation function of type Aggregator b b' -- -> QueryArr a b -> QueryArr a b'. Such a function would -- allow violation of SQL's scoping rules and lead to invalid queries. -- -- Please note that when aggregating an empty query with no GROUP -- BY clause, Opaleye's behaviour differs from Postgres's behaviour. -- Postgres returns a single row whereas Opaleye returns zero rows. -- (Opaleye's behaviour is consistent with the meaning of aggregating -- over groups of rows and Postgres's behaviour is inconsistent. When a -- query has zero rows it has zero groups, and thus zero rows in the -- result of an aggregation.) aggregate :: Aggregator a b -> Query a -> Query b -- | Order the values within each aggregation in Aggregator using -- the given ordering. This is only relevant for aggregations that depend -- on the order they get their elements, like arrayAgg and -- stringAgg. -- -- Note that this orders all aggregations with the same ordering. If you -- need different orderings for different aggregations, use -- orderAggregate. aggregateOrdered :: Order a -> Aggregator a b -> Query a -> Query b -- | Group the aggregation by equality on the input to groupBy. groupBy :: Aggregator (Column a) (Column a) -- | Sum all rows in a group. sum :: Aggregator (Column a) (Column a) -- | Count the number of non-null rows in a group. count :: Aggregator (Column a) (Column PGInt8) -- | Count the number of rows in a group. This Aggregator is named -- countStar after SQL's COUNT(*) aggregation function. countStar :: Aggregator a (Column PGInt8) -- | Average of a group avg :: Aggregator (Column PGFloat8) (Column PGFloat8) -- | Maximum of a group max :: PGOrd a => Aggregator (Column a) (Column a) -- | Maximum of a group min :: PGOrd a => Aggregator (Column a) (Column a) boolOr :: Aggregator (Column PGBool) (Column PGBool) boolAnd :: Aggregator (Column PGBool) (Column PGBool) arrayAgg :: Aggregator (Column a) (Column (PGArray a)) stringAgg :: Column PGText -> Aggregator (Column PGText) (Column PGText) -- | Count the number of rows in a query. This is different from -- aggregate count because it always returns exactly one -- row, even when the input query is empty. countRows :: Query a -> Query (Column PGInt8) -- | An Aggregator takes a collection of rows of type a, -- groups them, and transforms each group into a single row of type -- b. This corresponds to aggregators using GROUP BY in -- SQL. -- -- An Aggregator corresponds closely to a Fold from the -- foldl package. Whereas an Aggregator a -- b takes each group of type a to a single row of type -- b, a Fold a b takes a list of -- a and returns a single row of type b. data Aggregator a b module Opaleye.Internal.Distinct distinctExplicit :: Distinctspec columns columns' -> Query columns -> Query columns' newtype Distinctspec a b Distinctspec :: (Aggregator a b) -> Distinctspec a b instance Data.Profunctor.Product.Default.Class.Default Opaleye.Internal.Distinct.Distinctspec (Opaleye.Internal.Column.Column a) (Opaleye.Internal.Column.Column a) instance GHC.Base.Functor (Opaleye.Internal.Distinct.Distinctspec a) instance GHC.Base.Applicative (Opaleye.Internal.Distinct.Distinctspec a) instance Data.Profunctor.Unsafe.Profunctor Opaleye.Internal.Distinct.Distinctspec instance Data.Profunctor.Product.Class.ProductProfunctor Opaleye.Internal.Distinct.Distinctspec instance Data.Profunctor.Product.SumProfunctor Opaleye.Internal.Distinct.Distinctspec module Opaleye.Distinct -- | Remove duplicate rows from the Query. -- -- Example type specialization: -- --
--   distinct :: Query (Column a, Column b) -> Query (Column a, Column b)
--   
-- -- Assuming the makeAdaptorAndInstance splice has been run for -- the product type Foo: -- --
--   distinct :: Query (Foo (Column a) (Column b) (Column c)) -> Query (Foo (Column a) (Column b) (Column c))
--   
-- -- By design there is no distinct function of type QueryArr -- a b -> QueryArr a b. Such a function would allow violation of -- SQL's scoping rules and lead to invalid queries. distinct :: Default Distinctspec columns columns => Query columns -> Query columns distinctExplicit :: Distinctspec columns columns' -> Query columns -> Query columns' -- | Operators on Columns. Please note that numeric Column -- types are instances of Num, so you can use *, /, -- +, - on them. module Opaleye.Operators -- | Restrict query results to a particular condition. Corresponds to the -- guard method of the MonadPlus class. You would typically use -- restrict if you want to use Arrow notation. restrict :: QueryArr (Column PGBool) () -- | Filter a QueryArr to only those rows where the given condition -- holds. This is the QueryArr equivalent of filter from -- the Prelude. You would typically use keepWhen if you -- want to use a "point free" style. keepWhen :: (a -> Column PGBool) -> QueryArr a a (.==) :: Column a -> Column a -> Column PGBool infix 4 .== (./=) :: Column a -> Column a -> Column PGBool infix 4 ./= -- | A polymorphic equality operator that works for all types that you have -- run makeAdaptorAndInstance on. This may be unified with -- .== in a future version. (.===) :: Default EqPP columns columns => columns -> columns -> Column PGBool infix 4 .=== -- | A polymorphic inequality operator that works for all types that you -- have run makeAdaptorAndInstance on. This may be unified with -- .== in a future version. (./==) :: Default EqPP columns columns => columns -> columns -> Column PGBool infix 4 ./== (.>) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 .> (.<) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 .< (.<=) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 .<= (.>=) :: PGOrd a => Column a -> Column a -> Column PGBool infix 4 .>= quot_ :: PGIntegral a => Column a -> Column a -> Column a rem_ :: PGIntegral a => Column a -> Column a -> Column a case_ :: [(Column PGBool, Column a)] -> Column a -> Column a ifThenElse :: Column PGBool -> Column a -> Column a -> Column a -- | Boolean or (.||) :: Column PGBool -> Column PGBool -> Column PGBool infixr 2 .|| not :: Column PGBool -> Column PGBool -- | Concatenate Column PGText (.++) :: Column PGText -> Column PGText -> Column PGText -- | To lowercase lower :: Column PGText -> Column PGText -- | To uppercase upper :: Column PGText -> Column PGText -- | Postgres LIKE operator like :: Column PGText -> Column PGText -> Column PGBool charLength :: PGString a => Column a -> Column Int -- | True when any element of the container is true ors :: Foldable f => f (Column PGBool) -> Column PGBool -- | in_ is designed to be used in prefix form. -- -- in_ validProducts product checks whether -- product is a valid product. in_ validProducts -- is a function which checks whether a product is a valid product. in_ :: (Functor f, Foldable f) => f (Column a) -> Column a -> Column PGBool -- | True if the first argument occurs amongst the rows of the second, -- false otherwise. -- -- This operation is equivalent to Postgres's IN operator but, -- for expediency, is currently implemented using a LEFT JOIN. -- Please file a bug if this causes any issues in practice. inQuery :: Default EqPP columns columns => columns -> QueryArr () columns -> Query (Column PGBool) timestamptzAtTimeZone :: Column PGTimestamptz -> Column PGText -> Column PGTimestamp emptyArray :: IsSqlType a => Column (PGArray a) arrayPrepend :: Column a -> Column (PGArray a) -> Column (PGArray a) singletonArray :: IsSqlType a => Column a -> Column (PGArray a) -- | Class of Postgres types that represent json values. -- -- Used to overload functions and operators that work on both -- PGJson and PGJsonb. -- -- Warning: making additional instances of this class can lead to broken -- code! class PGIsJson a -- | Class of Postgres types that can be used to index json values. -- -- Warning: making additional instances of this class can lead to broken -- code! class PGJsonIndex a -- | Get JSON object field by key. (.->) :: (PGIsJson a, PGJsonIndex k) => Column (Nullable a) -> Column k -> Column (Nullable a) infixl 8 .-> -- | Get JSON object field as text. (.->>) :: (PGIsJson a, PGJsonIndex k) => Column (Nullable a) -> Column k -> Column (Nullable PGText) infixl 8 .->> -- | Get JSON object at specified path. (.#>) :: (PGIsJson a) => Column (Nullable a) -> Column (PGArray PGText) -> Column (Nullable a) infixl 8 .#> -- | Get JSON object at specified path as text. (.#>>) :: (PGIsJson a) => Column (Nullable a) -> Column (PGArray PGText) -> Column (Nullable PGText) infixl 8 .#>> -- | Does the left JSON value contain within it the right value? (.@>) :: Column PGJsonb -> Column PGJsonb -> Column PGBool infix 4 .@> -- | Is the left JSON value contained within the right value? (.<@) :: Column PGJsonb -> Column PGJsonb -> Column PGBool infix 4 .<@ -- | Does the key/element string exist within the JSON value? (.?) :: Column PGJsonb -> Column PGText -> Column PGBool infix 4 .? -- | Do any of these key/element strings exist? (.?|) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool infix 4 .?| -- | Do all of these key/element strings exist? (.?&) :: Column PGJsonb -> Column (PGArray PGText) -> Column PGBool infix 4 .?& -- | Cast a PGInt4 to a PGFloat8 doubleOfInt :: Column PGInt4 -> Column PGFloat8 -- | Boolean and (.&&) :: Column PGBool -> Column PGBool -> Column PGBool infixr 3 .&& instance Opaleye.Operators.PGIsJson Opaleye.PGTypes.PGJson instance Opaleye.Operators.PGIsJson Opaleye.PGTypes.PGJsonb instance Opaleye.Operators.PGJsonIndex Opaleye.PGTypes.PGInt4 instance Opaleye.Operators.PGJsonIndex Opaleye.PGTypes.PGInt8 instance Opaleye.Operators.PGJsonIndex Opaleye.PGTypes.PGText module Opaleye