Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Beam.Postgres
Description
Postgres is a popular, open-source RDBMS. It is fairly standards compliant and supports many advanced features and data types.
The beam-postgres
module is built atop of postgresql-simple
, which is
used for connection management, transaction support, serialization, and
deserialization.
beam-postgres
supports most beam features as well as many postgres-specific
features. For example, beam-postgres
provides support for full-text search,
DISTINCT ON
, JSON handling, postgres ARRAY
s, RANGE
s, and the MONEY
type.
The documentation for beam-postgres
functionality below indicates which
postgres function each function or type wraps. Postgres maintains its own
in-depth documentation. Please refer to that for more detailed information on
behavior.
For examples on how to use beam-postgres
usage, see
its manual.
Synopsis
- data Postgres = Postgres
- data Pg a
- liftIOWithHandle :: (Connection -> IO a) -> Pg a
- runBeamPostgres :: Connection -> Pg a -> IO a
- runBeamPostgresDebug :: (String -> IO ()) -> Connection -> Pg a -> IO a
- data PgCommandSyntax
- data PgSyntax
- data PgSelectSyntax
- data PgInsertSyntax
- data PgUpdateSyntax
- data PgDeleteSyntax
- postgresUriSyntax :: c Postgres Connection Pg -> BeamURIOpeners c
- json :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSON a)
- jsonb :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSONB a)
- uuid :: DataType Postgres UUID
- money :: DataType Postgres PgMoney
- tsquery :: DataType Postgres TsQuery
- tsvector :: DataType Postgres TsVector
- text :: DataType Postgres Text
- bytea :: DataType Postgres ByteString
- unboundedArray :: Typeable a => DataType Postgres a -> DataType Postgres (Vector a)
- smallserial :: Integral a => DataType Postgres (SqlSerial a)
- serial :: Integral a => DataType Postgres (SqlSerial a)
- bigserial :: Integral a => DataType Postgres (SqlSerial a)
- (@>) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s Bool
- (<@) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s Bool
- withoutKeys :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b)
- data PgBoundType
- exclusive :: a -> PgRangeBound a
- data TsVectorConfig
- newtype TsVector = TsVector ByteString
- toTsVector :: BeamSqlBackendIsString Postgres str => Maybe TsVectorConfig -> QGenExpr context Postgres s str -> QGenExpr context Postgres s TsVector
- english :: TsVectorConfig
- newtype TsQuery = TsQuery ByteString
- (@@) :: QGenExpr context Postgres s TsVector -> QGenExpr context Postgres s TsQuery -> QGenExpr context Postgres s Bool
- toTsQuery :: BeamSqlBackendIsString Postgres str => Maybe TsVectorConfig -> QGenExpr context Postgres s str -> QGenExpr context Postgres s TsQuery
- newtype PgJSON a = PgJSON a
- newtype PgJSONB a = PgJSONB a
- class IsPgJSON (json :: Type -> Type) where
- pgJsonEach :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (json Value)))
- pgJsonEachText :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text))
- pgJsonKeys :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey)
- pgJsonArrayElements :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (json Value)))
- pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text))
- pgJsonTypeOf :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text
- pgJsonStripNulls :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (json b)
- pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (json a)
- pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (json a)
- data PgJSONEach valType (f :: Type -> Type) = PgJSONEach {
- pgJsonEachKey :: C f Text
- pgJsonEachValue :: C f valType
- data PgJSONKey (f :: Type -> Type) = PgJSONKey {}
- data PgJSONElement a (f :: Type -> Type) = PgJSONElement {
- pgJsonElement :: C f a
- (->#) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s (json b)
- (->$) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s (json b)
- (->>#) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s Text
- (->>$) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s Text
- (#>) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (json b)
- (#>>) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Text
- (?) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s Bool
- (?|) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Bool
- (?&) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Bool
- withoutKey :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s (PgJSONB b)
- withoutIdx :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s (PgJSONB b)
- pgJsonArrayLength :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32
- pgArrayToJson :: QGenExpr ctxt Postgres s (Vector e) -> QGenExpr ctxt Postgres s (PgJSON a)
- pgJsonbUpdate :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s (PgJSONB a)
- pgJsonbSet :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s (PgJSONB a)
- pgJsonbPretty :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text
- newtype PgMoney = PgMoney {}
- pgMoney :: Real a => a -> PgMoney
- pgScaleMoney_ :: Num a => QGenExpr context Postgres s a -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney
- pgDivideMoney_ :: Num a => QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s a -> QGenExpr context Postgres s PgMoney
- pgDivideMoneys_ :: Num a => QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s a
- pgAddMoney_ :: QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney
- pgSubtractMoney_ :: QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney
- pgSumMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney
- pgAvgMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney
- pgSumMoney_ :: QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney
- pgAvgMoney_ :: QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney
- data PgPoint = PgPoint !Double !Double
- data PgLine = PgLine !Double !Double !Double
- data PgLineSegment = PgLineSegment !PgPoint !PgPoint
- data PgBox = PgBox !PgPoint !PgPoint
- data PgPath
- data PgPolygon = PgPolygon (NonEmpty PgPoint)
- data PgCircle = PgCircle !PgPoint !Double
- newtype PgRegex = PgRegex Text
- pgRegex_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex
- (~.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool
- (~*.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool
- (!~.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool
- (!~*.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool
- pgRegexpReplace_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s txt
- pgRegexpMatch_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s (Maybe (Vector text))
- pgRegexpSplitToTable :: forall text ctxt s (db :: (Type -> Type) -> Type). BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> Q Postgres db s (QExpr Postgres s Text)
- pgRegexpSplitToArray :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s (Vector text)
- data PgSetOf (tbl :: (Type -> Type) -> Type)
- pgUnnest :: forall tbl (db :: (Type -> Type) -> Type) s. Beamable tbl => QExpr Postgres s (PgSetOf tbl) -> Q Postgres db s (QExprTable Postgres s tbl)
- pgUnnestArray :: forall s a (db :: (Type -> Type) -> Type). QExpr Postgres s (Vector a) -> Q Postgres db s (QExpr Postgres s a)
- pgUnnestArrayWithOrdinality :: forall s a (db :: (Type -> Type) -> Type). QExpr Postgres s (Vector a) -> Q Postgres db s (QExpr Postgres s Int64, QExpr Postgres s a)
- data PgArrayValueContext
- class PgIsArrayContext (ctxt :: k)
- array_ :: (PgIsArrayContext context, Foldable f) => f (QGenExpr context Postgres s a) -> QGenExpr context Postgres s (Vector a)
- arrayOf_ :: forall (db :: (Type -> Type) -> Type) s a context. Q Postgres db s (QExpr Postgres s a) -> QGenExpr context Postgres s (Vector a)
- (++.) :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a)
- pgArrayAgg :: QExpr Postgres s a -> QAgg Postgres s (Vector a)
- pgArrayAggOver :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s a -> QAgg Postgres s (Vector a)
- (!.) :: Integral ix => QGenExpr context Postgres s (Vector a) -> QGenExpr context Postgres s ix -> QGenExpr context Postgres s a
- arrayDims_ :: BeamSqlBackendIsString Postgres text => QGenExpr context Postgres s (Vector a) -> QGenExpr context Postgres s text
- arrayUpper_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s num
- arrayLower_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s num
- arrayUpperUnsafe_ :: (Integral dim, Integral length) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s dim -> QGenExpr context Postgres s (Maybe length)
- arrayLowerUnsafe_ :: (Integral dim, Integral length) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s dim -> QGenExpr context Postgres s (Maybe length)
- arrayLength_ :: forall (dim :: Nat) ctxt num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr ctxt Postgres s (Vector v) -> QGenExpr ctxt Postgres s num
- arrayLengthUnsafe_ :: (Integral dim, Integral num) => QGenExpr ctxt Postgres s (Vector v) -> QGenExpr ctxt Postgres s dim -> QGenExpr ctxt Postgres s (Maybe num)
- isSupersetOf_ :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s Bool
- isSubsetOf_ :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s Bool
- data PgRange n a
- = PgEmptyRange
- | PgRange (PgRangeBound a) (PgRangeBound a)
- data PgRangeBound a = PgRangeBound PgBoundType (Maybe a)
- class PgIsRange (n :: k) where
- data PgInt4Range
- data PgInt8Range
- data PgNumRange
- data PgTsRange
- data PgTsTzRange
- data PgDateRange
- range_ :: forall n a context s. PgIsRange n => PgBoundType -> PgBoundType -> QGenExpr context Postgres s (Maybe a) -> QGenExpr context Postgres s (Maybe a) -> QGenExpr context Postgres s (PgRange n a)
- inclusive :: a -> PgRangeBound a
- unbounded :: PgRangeBound a
- (-@>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-@>) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s a -> QGenExpr context Postgres s Bool
- (-<@-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (<@-) :: QGenExpr context Postgres s a -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-&&-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-<<-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (->>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-&<-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-&>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (--|--) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- (-+-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a)
- (-*-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a)
- (-.-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a)
- rLower_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (Maybe a)
- rUpper_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (Maybe a)
- isEmpty_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- lowerInc_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- upperInc_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- lowerInf_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- upperInf_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool
- rangeMerge_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a)
- century_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- decade_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- dow_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- doy_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- epoch_ :: HasSqlTime tgt => ExtractField Postgres tgt NominalDiffTime
- isodow_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- isoyear_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- microseconds_ :: HasSqlTime tgt => ExtractField Postgres tgt Int32
- milliseconds_ :: HasSqlTime tgt => ExtractField Postgres tgt Int32
- millennium_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- quarter_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- week_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32
- pgBoolOr :: QExpr Postgres s a -> QAgg Postgres s (Maybe Bool)
- pgBoolAnd :: QExpr Postgres s a -> QAgg Postgres s (Maybe Bool)
- pgStringAgg :: BeamSqlBackendIsString Postgres str => QExpr Postgres s str -> QExpr Postgres s str -> QAgg Postgres s (Maybe str)
- pgStringAggOver :: BeamSqlBackendIsString Postgres str => Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s str -> QExpr Postgres s str -> QAgg Postgres s (Maybe str)
- pgNubBy_ :: forall key r (db :: (Type -> Type) -> Type) s. (Projectible Postgres key, Projectible Postgres r) => (r -> key) -> Q Postgres db s r -> Q Postgres db s r
- now_ :: QExpr Postgres s LocalTime
- ilike_ :: BeamSqlBackendIsString Postgres text => QExpr Postgres s text -> QExpr Postgres s text -> QExpr Postgres s Bool
- ilike_' :: (BeamSqlBackendIsString Postgres left, BeamSqlBackendIsString Postgres right) => QExpr Postgres s left -> QExpr Postgres s right -> QExpr Postgres s Bool
- data PgExtensionEntity extension
- class IsPgExtension extension where
- pgExtensionName :: Proxy extension -> Text
- pgExtensionBuild :: extension
- pgCreateExtension :: forall extension (db :: (Type -> Type) -> Type). IsPgExtension extension => Migration Postgres (CheckedDatabaseEntity Postgres db (PgExtensionEntity extension))
- pgDropExtension :: CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> Migration Postgres ()
- getPgExtension :: forall (db :: (Type -> Type) -> Type) extension. DatabaseEntity Postgres db (PgExtensionEntity extension) -> extension
- fromPgIntegral :: (FromField a, Integral a, Typeable a) => FromBackendRowM Postgres a
- fromPgScientificOrIntegral :: (Bounded a, Integral a) => FromBackendRowM Postgres a
- class PgDebugStmt statement
- pgTraceStmtIO :: PgDebugStmt statement => Connection -> statement -> IO ()
- pgTraceStmtIO' :: PgDebugStmt statement => Connection -> statement -> IO ByteString
- pgTraceStmt :: PgDebugStmt statement => statement -> Pg ()
- data ResultError
- = Incompatible { }
- | UnexpectedNull { }
- | ConversionFailed { }
- data SqlError = SqlError {}
- data Connection
- data ConnectInfo = ConnectInfo {}
- defaultConnectInfo :: ConnectInfo
- connectPostgreSQL :: ByteString -> IO Connection
- connect :: ConnectInfo -> IO Connection
- close :: Connection -> IO ()
Beam Postgres backend
The Postgres backend type, used to parameterize MonadBeam
. See the
definitions there for more information. The corresponding query monad is
Pg
. See documentation for MonadBeam
and the
user guide for more information on using
this backend.
Constructors
Postgres |
Instances
MonadBeam
in which we can run Postgres commands. See the documentation
for MonadBeam
on examples of how to use.
beam-postgres
also provides functions that let you run queries without
MonadBeam
. These functions may be more efficient and offer a conduit
API. See Database.Beam.Postgres.Conduit for more information.
You can execute Pg
actions using runBeamPostgres
or runBeamPostgresDebug
.
Instances
MonadFail Pg Source # | |
Defined in Database.Beam.Postgres.Connection | |
MonadIO Pg Source # | |
Defined in Database.Beam.Postgres.Connection | |
Applicative Pg Source # | |
Functor Pg Source # | |
Monad Pg Source # | |
MonadBeam Postgres Pg Source # | |
Defined in Database.Beam.Postgres.Connection Methods runReturningMany :: FromBackendRow Postgres x => BeamSqlBackendSyntax Postgres -> (Pg (Maybe x) -> Pg a) -> Pg a # runNoReturn :: BeamSqlBackendSyntax Postgres -> Pg () # runReturningOne :: FromBackendRow Postgres x => BeamSqlBackendSyntax Postgres -> Pg (Maybe x) # runReturningFirst :: FromBackendRow Postgres x => BeamSqlBackendSyntax Postgres -> Pg (Maybe x) # runReturningList :: FromBackendRow Postgres x => BeamSqlBackendSyntax Postgres -> Pg [x] # | |
MonadBeamDeleteReturning Postgres Pg Source # | |
Defined in Database.Beam.Postgres.Connection Methods runDeleteReturningList :: (Beamable table, Projectible Postgres (table (QExpr Postgres ())), FromBackendRow Postgres (table Identity)) => SqlDelete Postgres table -> Pg [table Identity] # | |
MonadBeamInsertReturning Postgres Pg Source # | |
Defined in Database.Beam.Postgres.Connection Methods runInsertReturningList :: (Beamable table, Projectible Postgres (table (QExpr Postgres ())), FromBackendRow Postgres (table Identity)) => SqlInsert Postgres table -> Pg [table Identity] # | |
MonadBeamUpdateReturning Postgres Pg Source # | |
Defined in Database.Beam.Postgres.Connection Methods runUpdateReturningList :: (Beamable table, Projectible Postgres (table (QExpr Postgres ())), FromBackendRow Postgres (table Identity)) => SqlUpdate Postgres table -> Pg [table Identity] # | |
MonadBaseControl IO Pg Source # | |
MonadBase IO Pg Source # | |
Defined in Database.Beam.Postgres.Connection | |
type StM Pg a Source # | |
Defined in Database.Beam.Postgres.Connection |
liftIOWithHandle :: (Connection -> IO a) -> Pg a Source #
Executing actions against the backend
runBeamPostgres :: Connection -> Pg a -> IO a Source #
runBeamPostgresDebug :: (String -> IO ()) -> Connection -> Pg a -> IO a Source #
Postgres syntax
data PgCommandSyntax Source #
Representation of an arbitrary Postgres command. This is the combination of
the command syntax (repesented by PgSyntax
), as well as the type of command
(represented by PgCommandType
). The command type is necessary for us to
know how to retrieve results from the database.
Instances
IsSql92Syntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
| |||||||||||||||||
IsSql92DdlCommandSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
| |||||||||||||||||
IsSql92DdlSchemaCommandSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
| |||||||||||||||||
type Sql92DeleteSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||||||||||
type Sql92InsertSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||||||||||
type Sql92SelectSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||||||||||
type Sql92UpdateSyntax PgCommandSyntax Source # | |||||||||||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||||||||||
type Sql92DdlCommandAlterTableSyntax PgCommandSyntax Source # | |||||||||||||||||
type Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax Source # | |||||||||||||||||
type Sql92DdlCommandCreateTableSyntax PgCommandSyntax Source # | |||||||||||||||||
type Sql92DdlCommandDropSchemaSyntax PgCommandSyntax Source # | |||||||||||||||||
type Sql92DdlCommandDropTableSyntax PgCommandSyntax Source # | |||||||||||||||||
A piece of Postgres SQL syntax, which may contain embedded escaped byte and
text sequences. PgSyntax
composes monoidally, and may be created with
emit
, emitBuilder
, escapeString
, escapBytea
, and escapeIdentifier
.
data PgSelectSyntax Source #
IsSql92SelectSyntax
for Postgres
Instances
IsSql92SelectSyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
Methods selectStmt :: Sql92SelectSelectTableSyntax PgSelectSyntax -> [Sql92SelectOrderingSyntax PgSelectSyntax] -> Maybe Integer -> Maybe Integer -> PgSelectSyntax # | |||||||||
IsSql99CommonTableExpressionSelectSyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
Methods withSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax # | |||||||||
IsSql99RecursiveCommonTableExpressionSelectSyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax Methods withRecursiveSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax # | |||||||||
type Sql92SelectOrderingSyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||
type Sql92SelectSelectTableSyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax | |||||||||
type Sql99SelectCTESyntax PgSelectSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax |
data PgInsertSyntax Source #
IsSql92InsertSyntax
for Postgres
Instances
IsSql92InsertSyntax PgInsertSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
Methods insertStmt :: Sql92InsertTableNameSyntax PgInsertSyntax -> [Text] -> Sql92InsertValuesSyntax PgInsertSyntax -> PgInsertSyntax # | |||||||||
type Sql92InsertTableNameSyntax PgInsertSyntax Source # | |||||||||
type Sql92InsertValuesSyntax PgInsertSyntax Source # | |||||||||
data PgUpdateSyntax Source #
IsSql92UpdateSyntax
for Postgres
Instances
IsSql92UpdateSyntax PgUpdateSyntax Source # | |||||||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
| |||||||||||||
type Sql92UpdateExpressionSyntax PgUpdateSyntax Source # | |||||||||||||
type Sql92UpdateFieldNameSyntax PgUpdateSyntax Source # | |||||||||||||
type Sql92UpdateTableNameSyntax PgUpdateSyntax Source # | |||||||||||||
data PgDeleteSyntax Source #
IsSql92DeleteSyntax
for Postgres
Instances
IsSql92DeleteSyntax PgDeleteSyntax Source # | |||||||||
Defined in Database.Beam.Postgres.Syntax Associated Types
| |||||||||
type Sql92DeleteExpressionSyntax PgDeleteSyntax Source # | |||||||||
type Sql92DeleteTableNameSyntax PgDeleteSyntax Source # | |||||||||
Beam URI support
postgresUriSyntax :: c Postgres Connection Pg -> BeamURIOpeners c Source #
BeamURIOpeners
for the standard postgresql:
URI scheme. See the
postgres documentation for more details on the formatting. See documentation
for BeamURIOpeners
for more information on how to use this with beam
Postgres-specific features
Postgres-specific data types
uuid :: DataType Postgres UUID Source #
DataType
for UUID
columns. The pgCryptoGenRandomUUID
function in
the PgCrypto
extension can be used to generate UUIDs at random.
text :: DataType Postgres Text Source #
DataType
for Postgres TEXT
. characterLargeObject
is also mapped to
this data type
bytea :: DataType Postgres ByteString Source #
DataType
for Postgres BYTEA
. binaryLargeObject
is also mapped to
this data type
unboundedArray :: Typeable a => DataType Postgres a -> DataType Postgres (Vector a) Source #
DataType
for a Postgres array without any bounds.
Note that array support in beam-migrate
is still incomplete.
SERIAL
support
smallserial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL
data types. Automatically generates an appropriate
DEFAULT
clause and sequence
serial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL
data types. Automatically generates an appropriate
DEFAULT
clause and sequence
bigserial :: Integral a => DataType Postgres (SqlSerial a) Source #
Postgres SERIAL
data types. Automatically generates an appropriate
DEFAULT
clause and sequence
(@>) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s Bool Source #
Postgres @>
and <@
operators for JSON. Return true if the
json object pointed to by the arrow is completely contained in the other. See
the Postgres documentation for more in formation on what this means.
(<@) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s Bool Source #
Postgres @>
and <@
operators for JSON. Return true if the
json object pointed to by the arrow is completely contained in the other. See
the Postgres documentation for more in formation on what this means.
withoutKeys :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b) Source #
Postgres #-
operator. Removes all the keys specificied from the JSON
object and returns the result.
data PgBoundType Source #
Represents the types of bounds a range can have. A range can and often does have mis-matched bound types.
Instances
Generic PgBoundType Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
| |||||
Show PgBoundType Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods showsPrec :: Int -> PgBoundType -> ShowS # show :: PgBoundType -> String # showList :: [PgBoundType] -> ShowS # | |||||
Eq PgBoundType Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific | |||||
Hashable PgBoundType Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific | |||||
type Rep PgBoundType Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific |
exclusive :: a -> PgRangeBound a Source #
data TsVectorConfig Source #
The identifier of a Postgres text search configuration.
Use the IsString
instance to construct new values of this type
Instances
IsString TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromString :: String -> TsVectorConfig # | |
Show TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods showsPrec :: Int -> TsVectorConfig -> ShowS # show :: TsVectorConfig -> String # showList :: [TsVectorConfig] -> ShowS # | |
Eq TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods (==) :: TsVectorConfig -> TsVectorConfig -> Bool # (/=) :: TsVectorConfig -> TsVectorConfig -> Bool # | |
Ord TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods compare :: TsVectorConfig -> TsVectorConfig -> Ordering # (<) :: TsVectorConfig -> TsVectorConfig -> Bool # (<=) :: TsVectorConfig -> TsVectorConfig -> Bool # (>) :: TsVectorConfig -> TsVectorConfig -> Bool # (>=) :: TsVectorConfig -> TsVectorConfig -> Bool # max :: TsVectorConfig -> TsVectorConfig -> TsVectorConfig # min :: TsVectorConfig -> TsVectorConfig -> TsVectorConfig # | |
HasSqlEqualityCheck Postgres TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy TsVectorConfig -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy TsVectorConfig -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy TsVectorConfig -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy TsVectorConfig -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres TsVectorConfig Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy TsVectorConfig -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy TsVectorConfig -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # |
The type of a document preprocessed for full-text search. The contained
ByteString
is the Postgres representation of the TSVECTOR
type. Use
toTsVector
to construct these on-the-fly from strings.
When this field is embedded in a beam table, defaultMigratableDbSettings
will give the column the postgres TSVECTOR
type.
Constructors
TsVector ByteString |
Instances
Show TsVector Source # | |
Eq TsVector Source # | |
Ord TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromField TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
ToField TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromBackendRow Postgres TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlEqualityCheck Postgres TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy TsVector -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy TsVector -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy TsVector -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy TsVector -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy TsVector -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy TsVector -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasDefaultSqlDataType Postgres TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy TsVector -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy TsVector -> Proxy Postgres -> Bool -> [FieldCheck] # |
toTsVector :: BeamSqlBackendIsString Postgres str => Maybe TsVectorConfig -> QGenExpr context Postgres s str -> QGenExpr context Postgres s TsVector Source #
The Postgres to_tsvector
function. Given a configuration and string,
return the TSVECTOR
that represents the contents of the string.
english :: TsVectorConfig Source #
A full-text search configuration with sensible defaults for english
A query that can be run against a document contained in a TsVector
.
When this field is embedded in a beam table, defaultMigratableDbSettings
will give the column the postgres TSVECTOR
type
Constructors
TsQuery ByteString |
Instances
Show TsQuery Source # | |
Eq TsQuery Source # | |
Ord TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromField TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
FromBackendRow Postgres TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlEqualityCheck Postgres TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy TsQuery -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy TsQuery -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy TsQuery -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy TsQuery -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy TsQuery -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy TsQuery -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasDefaultSqlDataType Postgres TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy TsQuery -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy TsQuery -> Proxy Postgres -> Bool -> [FieldCheck] # |
(@@) :: QGenExpr context Postgres s TsVector -> QGenExpr context Postgres s TsQuery -> QGenExpr context Postgres s Bool Source #
Determine if the given TSQUERY
matches the document represented by the
TSVECTOR
. Behaves exactly like the similarly-named operator in postgres.
toTsQuery :: BeamSqlBackendIsString Postgres str => Maybe TsVectorConfig -> QGenExpr context Postgres s str -> QGenExpr context Postgres s TsQuery Source #
The Postgres to_tsquery
function. Given a configuration and string,
return the TSQUERY
that represents the contents of the string.
The Postgres JSON
type, which stores textual values that represent JSON
objects. The type parameter indicates the Haskell type which the JSON
encodes. This type must be a member of FromJSON
and ToJSON
in order for
deserialization and serialization to work as expected.
The defaultMigratableDbSettings
function automatically assigns the postgres
JSON
type to fields with this type.
Constructors
PgJSON a |
Instances
IsPgJSON PgJSON Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods pgJsonEach :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (PgJSON Value))) Source # pgJsonEachText :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text)) Source # pgJsonKeys :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey) Source # pgJsonArrayElements :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (PgJSON Value))) Source # pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text)) Source # pgJsonTypeOf :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s Text Source # pgJsonStripNulls :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgJSON b) Source # pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (PgJSON a) Source # pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (PgJSON a) Source # | |
(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgJSON a) # | |
ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgJSON a -> PgValueSyntax # | |
HasSqlEqualityCheck Postgres (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy (PgJSON a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy (PgJSON a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy (PgJSON a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy (PgJSON a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy (PgJSON a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy (PgJSON a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasDefaultSqlDataType Postgres (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy (PgJSON a) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy (PgJSON a) -> Proxy Postgres -> Bool -> [FieldCheck] # | |
Monoid a => Monoid (PgJSON a) Source # | |
Semigroup a => Semigroup (PgJSON a) Source # | |
Show a => Show (PgJSON a) Source # | |
Eq a => Eq (PgJSON a) Source # | |
Ord a => Ord (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
Hashable a => Hashable (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
(Typeable x, FromJSON x) => FromField (PgJSON x) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromField :: FieldParser (PgJSON x) # |
The Postgres JSONB
type, which stores JSON-encoded data in a
postgres-specific binary format. Like PgJSON
, the type parameter indicates
the Haskell type which the JSON encodes.
Fields with this type are automatically given the Postgres JSONB
type
Constructors
PgJSONB a |
Instances
IsPgJSON PgJSONB Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods pgJsonEach :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (PgJSONB Value))) Source # pgJsonEachText :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text)) Source # pgJsonKeys :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey) Source # pgJsonArrayElements :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (PgJSONB Value))) Source # pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text)) Source # pgJsonTypeOf :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text Source # pgJsonStripNulls :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) Source # pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (PgJSONB a) Source # pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (PgJSONB a) Source # | |
(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgJSONB a) # valuesNeeded :: Proxy Postgres -> Proxy (PgJSONB a) -> Int # | |
ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgJSONB a -> PgValueSyntax # | |
HasSqlEqualityCheck Postgres (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy (PgJSONB a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy (PgJSONB a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy (PgJSONB a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy (PgJSONB a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy (PgJSONB a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy (PgJSONB a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasDefaultSqlDataType Postgres (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy (PgJSONB a) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy (PgJSONB a) -> Proxy Postgres -> Bool -> [FieldCheck] # | |
Monoid a => Monoid (PgJSONB a) Source # | |
Semigroup a => Semigroup (PgJSONB a) Source # | |
Show a => Show (PgJSONB a) Source # | |
Eq a => Eq (PgJSONB a) Source # | |
Ord a => Ord (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
Hashable a => Hashable (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
(Typeable x, FromJSON x) => FromField (PgJSONB x) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromField :: FieldParser (PgJSONB x) # |
class IsPgJSON (json :: Type -> Type) where Source #
Postgres provides separate json_
and jsonb_
functions. However, we know
what we're dealing with based on the type of data, so we can be less obtuse.
For more information on how these functions behave, see the Postgres manual section on JSON.
Methods
pgJsonEach :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (json Value))) Source #
The json_each
or jsonb_each
function. Values returned as json
or
jsonb
respectively. Use pgUnnest
to join against the result
pgJsonEachText :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text)) Source #
Like pgJsonEach
, but returning text values instead
pgJsonKeys :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey) Source #
The json_object_keys
and jsonb_object_keys
function. Use pgUnnest
to join against the result.
pgJsonArrayElements :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (json Value))) Source #
The json_array_elements
and jsonb_array_elements
function. Use
pgUnnest
to join against the result
pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text)) Source #
Like pgJsonArrayElements
, but returning the values as Text
pgJsonTypeOf :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text Source #
The json_typeof
or jsonb_typeof
function
pgJsonStripNulls :: QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (json b) Source #
The json_strip_nulls
or jsonb_strip_nulls
function.
pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (json a) Source #
The json_agg
or jsonb_agg
aggregate.
pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (json a) Source #
The json_object_agg
or jsonb_object_agg
. The first argument gives the
key source and the second the corresponding values.
Instances
IsPgJSON PgJSON Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods pgJsonEach :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (PgJSON Value))) Source # pgJsonEachText :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text)) Source # pgJsonKeys :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey) Source # pgJsonArrayElements :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (PgJSON Value))) Source # pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text)) Source # pgJsonTypeOf :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s Text Source # pgJsonStripNulls :: QGenExpr ctxt Postgres s (PgJSON a) -> QGenExpr ctxt Postgres s (PgJSON b) Source # pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (PgJSON a) Source # pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (PgJSON a) Source # | |
IsPgJSON PgJSONB Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods pgJsonEach :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach (PgJSONB Value))) Source # pgJsonEachText :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONEach Text)) Source # pgJsonKeys :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf PgJSONKey) Source # pgJsonArrayElements :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement (PgJSONB Value))) Source # pgJsonArrayElementsText :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgSetOf (PgJSONElement Text)) Source # pgJsonTypeOf :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text Source # pgJsonStripNulls :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (PgJSONB b) Source # pgJsonAgg :: QExpr Postgres s a -> QAgg Postgres s (PgJSONB a) Source # pgJsonObjectAgg :: QExpr Postgres s key -> QExpr Postgres s value -> QAgg Postgres s (PgJSONB a) Source # |
data PgJSONEach valType (f :: Type -> Type) Source #
Key-value pair, used as output of pgJsonEachText
and pgJsonEach
Constructors
PgJSONEach | |
Fields
|
Instances
Beamable (PgJSONEach valType) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> PgJSONEach valType f -> PgJSONEach valType g -> m (PgJSONEach valType h) # tblSkeleton :: TableSkeleton (PgJSONEach valType) # | |||||
Generic (PgJSONEach valType f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
Methods from :: PgJSONEach valType f -> Rep (PgJSONEach valType f) x # to :: Rep (PgJSONEach valType f) x -> PgJSONEach valType f # | |||||
type Rep (PgJSONEach valType f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific type Rep (PgJSONEach valType f) = D1 ('MetaData "PgJSONEach" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-9RY3FTbcpgg9tLiPshayrX" 'False) (C1 ('MetaCons "PgJSONEach" 'PrefixI 'True) (S1 ('MetaSel ('Just "pgJsonEachKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Text)) :*: S1 ('MetaSel ('Just "pgJsonEachValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f valType)))) |
data PgJSONKey (f :: Type -> Type) Source #
Output row of pgJsonKeys
Instances
Beamable PgJSONKey Source # | |||||
Generic (PgJSONKey f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
| |||||
type Rep (PgJSONKey f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific |
data PgJSONElement a (f :: Type -> Type) Source #
Output row of pgJsonArrayElements
and pgJsonArrayElementsText
Constructors
PgJSONElement | |
Fields
|
Instances
Beamable (PgJSONElement a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a0. Columnar' f a0 -> Columnar' g a0 -> m (Columnar' h a0)) -> PgJSONElement a f -> PgJSONElement a g -> m (PgJSONElement a h) # tblSkeleton :: TableSkeleton (PgJSONElement a) # | |||||
Generic (PgJSONElement a f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
Methods from :: PgJSONElement a f -> Rep (PgJSONElement a f) x # to :: Rep (PgJSONElement a f) x -> PgJSONElement a f # | |||||
type Rep (PgJSONElement a f) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific type Rep (PgJSONElement a f) = D1 ('MetaData "PgJSONElement" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-9RY3FTbcpgg9tLiPshayrX" 'False) (C1 ('MetaCons "PgJSONElement" 'PrefixI 'True) (S1 ('MetaSel ('Just "pgJsonElement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f a)))) |
(->#) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s (json b) Source #
Access a JSON array by index. Corresponds to the Postgres ->
operator.
See (->$)
for the corresponding operator for object access.
(->$) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s (json b) Source #
Acces a JSON object by key. Corresponds to the Postgres ->
operator. See
(->#)
for the corresponding operator for arrays.
(->>#) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s Text Source #
Access a JSON array by index, returning the embedded object as a string.
Corresponds to the Postgres ->>
operator. See (->>$)
for the
corresponding operator on objects.
(->>$) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s Text Source #
Access a JSON object by key, returning the embedded object as a string.
Corresponds to the Postgres ->>
operator. See (->>#)
for the
corresponding operator on arrays.
(#>) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (json b) Source #
Access a deeply nested JSON object. The first argument is the JSON object to look within, the second is the path of keys from the first argument to the target. Returns the result as a new json value. Note that the postgres function allows etiher string keys or integer indices, but this function only allows string keys. PRs to improve this functionality are welcome.
(#>>) :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Text Source #
Like (#>)
but returns the result as a string.
(?) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s Bool Source #
Postgres ?
operator. Checks if the given string exists as top-level key
of the json object.
(?|) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Bool Source #
Postgres ?|
and ?&
operators. Check if any or all of the given strings
exist as top-level keys of the json object respectively.
(?&) :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s Bool Source #
Postgres ?|
and ?&
operators. Check if any or all of the given strings
exist as top-level keys of the json object respectively.
withoutKey :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s (PgJSONB b) Source #
Postgres -
operator on json objects. Returns the supplied json object
with the supplied key deleted. See withoutIdx
for the corresponding
operator on arrays.
withoutIdx :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Int32 -> QGenExpr ctxt Postgres s (PgJSONB b) Source #
Postgres -
operator on json arrays. See withoutKey
for the
corresponding operator on objects.
pgJsonArrayLength :: IsPgJSON json => QGenExpr ctxt Postgres s (json a) -> QGenExpr ctxt Postgres s Int32 Source #
Postgres json_array_length
function. The supplied json object should be
an array, but this isn't checked at compile-time.
pgArrayToJson :: QGenExpr ctxt Postgres s (Vector e) -> QGenExpr ctxt Postgres s (PgJSON a) Source #
Postgres array_to_json
function.
pgJsonbUpdate :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s (PgJSONB a) Source #
The postgres jsonb_set
function. pgJsonUpdate
expects the value
specified by the path in the second argument to exist. If it does not, the
first argument is not modified. pgJsonbSet
will create any intermediate
objects necessary. This corresponds to the create_missing
argument of
jsonb_set
being set to false or true respectively.
pgJsonbSet :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s (Vector Text) -> QGenExpr ctxt Postgres s (PgJSONB b) -> QGenExpr ctxt Postgres s (PgJSONB a) Source #
The postgres jsonb_set
function. pgJsonUpdate
expects the value
specified by the path in the second argument to exist. If it does not, the
first argument is not modified. pgJsonbSet
will create any intermediate
objects necessary. This corresponds to the create_missing
argument of
jsonb_set
being set to false or true respectively.
pgJsonbPretty :: QGenExpr ctxt Postgres s (PgJSONB a) -> QGenExpr ctxt Postgres s Text Source #
Postgres jsonb_pretty
function
Postgres MONEY
data type. A simple wrapper over ByteString
, because
Postgres money format is locale-dependent, and we don't handle currency
symbol placement, digit grouping, or decimal separation.
The pgMoney
function can be used to convert a number to PgMoney
.
Constructors
PgMoney | |
Fields |
Instances
Read PgMoney Source # | |
Show PgMoney Source # | |
Eq PgMoney Source # | |
Ord PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromField PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
ToField PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromBackendRow Postgres PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgMoney -> PgValueSyntax # | |
HasSqlEqualityCheck Postgres PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy PgMoney -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy PgMoney -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy PgMoney -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy PgMoney -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasSqlQuantifiedEqualityCheck Postgres PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy PgMoney -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy PgMoney -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |
HasDefaultSqlDataType Postgres PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy PgMoney -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy PgMoney -> Proxy Postgres -> Bool -> [FieldCheck] # |
pgMoney :: Real a => a -> PgMoney Source #
Attempt to pack a floating point value as a PgMoney
value, paying no
attention to the locale-dependent currency symbol, digit grouping, or decimal
point. This will use the .
symbol as the decimal separator.
pgScaleMoney_ :: Num a => QGenExpr context Postgres s a -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney Source #
Multiply a MONEY
value by a numeric value. Corresponds to the Postgres
*
operator.
pgDivideMoney_ :: Num a => QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s a -> QGenExpr context Postgres s PgMoney Source #
Divide a MONEY
value by a numeric value. Corresponds to Postgres /
where the numerator has type MONEY
and the denominator is a number. If you
would like to divide two MONEY
values and have their units cancel out, use
pgDivideMoneys_
.
pgDivideMoneys_ :: Num a => QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s a Source #
Dividing two MONEY
value results in a number. Corresponds to Postgres /
on two MONEY
values. If you would like to divide MONEY
by a scalar, use pgDivideMoney_
pgAddMoney_ :: QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney Source #
Postgres +
and -
operators on money.
pgSubtractMoney_ :: QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney -> QGenExpr context Postgres s PgMoney Source #
Postgres +
and -
operators on money.
pgSumMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney Source #
The Postgres MONEY
type can be summed or averaged in an aggregation.
These functions provide the quantified aggregations. See pgSumMoney_
and
pgAvgMoney_
for the unquantified versions.
pgAvgMoneyOver_ :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney Source #
The Postgres MONEY
type can be summed or averaged in an aggregation.
These functions provide the quantified aggregations. See pgSumMoney_
and
pgAvgMoney_
for the unquantified versions.
pgSumMoney_ :: QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney Source #
The Postgres MONEY
type can be summed or averaged in an aggregation. To
provide an explicit quantification, see pgSumMoneyOver_
and
pgAvgMoneyOver_
.
pgAvgMoney_ :: QExpr Postgres s PgMoney -> QExpr Postgres s PgMoney Source #
The Postgres MONEY
type can be summed or averaged in an aggregation. To
provide an explicit quantification, see pgSumMoneyOver_
and
pgAvgMoneyOver_
.
Instances
Show PgPoint Source # | |
Eq PgPoint Source # | |
Ord PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
FromField PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
FromBackendRow Postgres PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgPoint -> PgValueSyntax # | |
HasDefaultSqlDataType Postgres PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy PgPoint -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy PgPoint -> Proxy Postgres -> Bool -> [FieldCheck] # |
Instances
Show PgLine Source # | |
Eq PgLine Source # | |
Ord PgLine Source # | |
HasSqlValueSyntax PgValueSyntax PgLine Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgLine -> PgValueSyntax # | |
HasDefaultSqlDataType Postgres PgLine Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy PgLine -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy PgLine -> Proxy Postgres -> Bool -> [FieldCheck] # |
data PgLineSegment Source #
Constructors
PgLineSegment !PgPoint !PgPoint |
Instances
Show PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods showsPrec :: Int -> PgLineSegment -> ShowS # show :: PgLineSegment -> String # showList :: [PgLineSegment] -> ShowS # | |
Eq PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods (==) :: PgLineSegment -> PgLineSegment -> Bool # (/=) :: PgLineSegment -> PgLineSegment -> Bool # | |
Ord PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods compare :: PgLineSegment -> PgLineSegment -> Ordering # (<) :: PgLineSegment -> PgLineSegment -> Bool # (<=) :: PgLineSegment -> PgLineSegment -> Bool # (>) :: PgLineSegment -> PgLineSegment -> Bool # (>=) :: PgLineSegment -> PgLineSegment -> Bool # max :: PgLineSegment -> PgLineSegment -> PgLineSegment # min :: PgLineSegment -> PgLineSegment -> PgLineSegment # | |
HasSqlValueSyntax PgValueSyntax PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasDefaultSqlDataType Postgres PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy PgLineSegment -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy PgLineSegment -> Proxy Postgres -> Bool -> [FieldCheck] # |
Instances
Show PgBox Source # | |
Eq PgBox Source # | |
FromField PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
FromBackendRow Postgres PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgBox -> PgValueSyntax # | |
HasDefaultSqlDataType Postgres PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods defaultSqlDataType :: Proxy PgBox -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres # defaultSqlDataTypeConstraints :: Proxy PgBox -> Proxy Postgres -> Bool -> [FieldCheck] # |
Constructors
PgPathOpen (NonEmpty PgPoint) | |
PgPathClosed (NonEmpty PgPoint) |
Instances
Show PgPolygon Source # | |
Eq PgPolygon Source # | |
Ord PgPolygon Source # | |
Defined in Database.Beam.Postgres.PgSpecific |
The type of Postgres regular expressions. Only a
HasSqlValueSyntax
instance is supplied, because you won't need to
be reading these back from the database.
If you're generating regexes dynamically, then use pgRegex_
to
convert a string expression into a regex one.
Instances
IsString PgRegex Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromString :: String -> PgRegex # | |
Show PgRegex Source # | |
Eq PgRegex Source # | |
Ord PgRegex Source # | |
Defined in Database.Beam.Postgres.PgSpecific | |
HasSqlValueSyntax PgValueSyntax PgRegex Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgRegex -> PgValueSyntax # |
pgRegex_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex Source #
Convert a string valued expression (which could be generated
dynamically) into a PgRegex
-typed one.
(~.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool Source #
Match regular expression, case-sensitive
(~*.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool Source #
Match regular expression, case-insensitive
(!~.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool Source #
Does not match regular expression, case-sensitive
(!~*.) :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s Bool Source #
Does not match regular expression, case-insensitive
pgRegexpReplace_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s Text -> QGenExpr ctxt Postgres s txt Source #
Postgres regexp_replace
. Replaces all instances of the regex in
the first argument with the third argument. The fourth argument is
the postgres regex options to provide.
pgRegexpMatch_ :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s (Maybe (Vector text)) Source #
Postgres regexp_match
. Matches the regular expression against
the string given and returns an array where each element
corresponds to a match in the string, or NULL
if nothing was
found
pgRegexpSplitToTable :: forall text ctxt s (db :: (Type -> Type) -> Type). BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> Q Postgres db s (QExpr Postgres s Text) Source #
Postgres regexp_split_to_table
. Splits the given string by the
given regex and return a result set that can be joined against.
pgRegexpSplitToArray :: BeamSqlBackendIsString Postgres text => QGenExpr ctxt Postgres s text -> QGenExpr ctxt Postgres s PgRegex -> QGenExpr ctxt Postgres s (Vector text) Source #
Postgres regexp_split_to_array
. Splits the given string by the
given regex and returns the result as an array.
pgUnnest :: forall tbl (db :: (Type -> Type) -> Type) s. Beamable tbl => QExpr Postgres s (PgSetOf tbl) -> Q Postgres db s (QExprTable Postgres s tbl) Source #
Join the results of the given set-valued function to the query
pgUnnestArray :: forall s a (db :: (Type -> Type) -> Type). QExpr Postgres s (Vector a) -> Q Postgres db s (QExpr Postgres s a) Source #
Introduce each element of the array as a row
pgUnnestArrayWithOrdinality :: forall s a (db :: (Type -> Type) -> Type). QExpr Postgres s (Vector a) -> Q Postgres db s (QExpr Postgres s Int64, QExpr Postgres s a) Source #
Introduce each element of the array as a row, along with the element's index
data PgArrayValueContext Source #
An expression context that determines which types of expressions can be put inside an array element. Any scalar, aggregate, or window expression can be placed within an array.
Instances
PgIsArrayContext PgArrayValueContext Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods mkArraySyntax :: Proxy PgArrayValueContext -> PgSyntax -> PgSyntax |
class PgIsArrayContext (ctxt :: k) Source #
If you are extending beam-postgres and provide another expression context that can be represented in an array, provide an empty instance of this class.
Instances
PgIsArrayContext QAggregateContext Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods mkArraySyntax :: Proxy QAggregateContext -> PgSyntax -> PgSyntax | |
PgIsArrayContext QValueContext Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods mkArraySyntax :: Proxy QValueContext -> PgSyntax -> PgSyntax | |
PgIsArrayContext QWindowingContext Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods mkArraySyntax :: Proxy QWindowingContext -> PgSyntax -> PgSyntax | |
PgIsArrayContext PgArrayValueContext Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods mkArraySyntax :: Proxy PgArrayValueContext -> PgSyntax -> PgSyntax |
array_ :: (PgIsArrayContext context, Foldable f) => f (QGenExpr context Postgres s a) -> QGenExpr context Postgres s (Vector a) Source #
Build a 1-dimensional postgres array from an arbitrary Foldable
containing expressions.
arrayOf_ :: forall (db :: (Type -> Type) -> Type) s a context. Q Postgres db s (QExpr Postgres s a) -> QGenExpr context Postgres s (Vector a) Source #
Build a 1-dimensional postgres array from a subquery
(++.) :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) Source #
Postgres ||
operator. Concatenates two vectors and returns their result.
pgArrayAgg :: QExpr Postgres s a -> QAgg Postgres s (Vector a) Source #
An aggregate that adds each value to the resulting array. See pgArrayOver
if you want to specify a quantifier. Corresponds to the Postgres ARRAY_AGG
function.
pgArrayAggOver :: Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s a -> QAgg Postgres s (Vector a) Source #
Postgres ARRAY_AGG
with an explicit quantifier. Includes each row that
meets the quantification criteria in the result.
(!.) :: Integral ix => QGenExpr context Postgres s (Vector a) -> QGenExpr context Postgres s ix -> QGenExpr context Postgres s a Source #
arrayDims_ :: BeamSqlBackendIsString Postgres text => QGenExpr context Postgres s (Vector a) -> QGenExpr context Postgres s text Source #
Postgres array_dims()
function. Returns a textual representation of the
dimensions of the array.
arrayUpper_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s num Source #
Return the upper or lower bound of the given array at the given dimension
(statically supplied as a type application on a Nat
). Note
that beam will attempt to statically determine if the dimension is in range.
GHC errors will be thrown if this cannot be proved.
For example, to get the upper bound of the 2nd-dimension of an array:
arrayUpper_ @2 vectorValuedExpression
arrayLower_ :: forall (dim :: Nat) context num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s num Source #
Return the upper or lower bound of the given array at the given dimension
(statically supplied as a type application on a Nat
). Note
that beam will attempt to statically determine if the dimension is in range.
GHC errors will be thrown if this cannot be proved.
For example, to get the upper bound of the 2nd-dimension of an array:
arrayUpper_ @2 vectorValuedExpression
arrayUpperUnsafe_ :: (Integral dim, Integral length) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s dim -> QGenExpr context Postgres s (Maybe length) Source #
These functions can be used to find the lower and upper bounds of an array where the dimension number is not known until run-time. They are marked unsafe because they may cause query processing to fail at runtime, even if they typecheck successfully.
arrayLowerUnsafe_ :: (Integral dim, Integral length) => QGenExpr context Postgres s (Vector v) -> QGenExpr context Postgres s dim -> QGenExpr context Postgres s (Maybe length) Source #
These functions can be used to find the lower and upper bounds of an array where the dimension number is not known until run-time. They are marked unsafe because they may cause query processing to fail at runtime, even if they typecheck successfully.
arrayLength_ :: forall (dim :: Nat) ctxt num v s. (KnownNat dim, WithinBounds dim (Vector v), Integral num) => QGenExpr ctxt Postgres s (Vector v) -> QGenExpr ctxt Postgres s num Source #
Get the size of the array at the given (statically known) dimension,
provided as a type-level Nat
. Like the arrayUpper_
and arrayLower_
functions,throws a compile-time error if the dimension is out of bounds.
arrayLengthUnsafe_ :: (Integral dim, Integral num) => QGenExpr ctxt Postgres s (Vector v) -> QGenExpr ctxt Postgres s dim -> QGenExpr ctxt Postgres s (Maybe num) Source #
Get the size of an array at a dimension not known until run-time. Marked unsafe as this may cause runtime errors even if it type checks.
isSupersetOf_ :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s Bool Source #
The Postgres @>
operator. Returns true if every member of the second
array is present in the first.
isSubsetOf_ :: QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s (Vector a) -> QGenExpr ctxt Postgres s Bool Source #
The Postgres <@
operator. Returns true if every member of the first
array is present in the second.
A range of a given Haskell type (represented by a
) stored as a given Postgres Range Type
(represented by n
).
A reasonable example might be Range PgInt8Range Int64
.
This represents a range of Haskell Int64
values stored as a range of bigint
in Postgres.
Constructors
PgEmptyRange | |
PgRange (PgRangeBound a) (PgRangeBound a) |
Instances
(FromField a, Typeable a, Typeable n, Ord a) => FromBackendRow Postgres (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgRange n a) # valuesNeeded :: Proxy Postgres -> Proxy (PgRange n a) -> Int # | |||||
(HasSqlValueSyntax PgValueSyntax a, PgIsRange n) => HasSqlValueSyntax PgValueSyntax (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgRange n a -> PgValueSyntax # | |||||
HasSqlEqualityCheck Postgres (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods sqlEqE :: Proxy (PgRange n a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqE :: Proxy (PgRange n a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlEqTriE :: Proxy (PgRange n a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlNeqTriE :: Proxy (PgRange n a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |||||
HasSqlQuantifiedEqualityCheck Postgres (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods sqlQEqE :: Proxy (PgRange n a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # sqlQNeqE :: Proxy (PgRange n a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres # | |||||
Generic (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
| |||||
Show a => Show (PgRange n a) Source # | |||||
Eq a => Eq (PgRange n a) Source # | |||||
Hashable a => Hashable (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific | |||||
(FromField a, Typeable a, Typeable n, Ord a) => FromField (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods fromField :: FieldParser (PgRange n a) # | |||||
ToField (PGRange a) => ToField (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific | |||||
type Rep (PgRange n a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific type Rep (PgRange n a) = D1 ('MetaData "PgRange" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-9RY3FTbcpgg9tLiPshayrX" 'False) (C1 ('MetaCons "PgEmptyRange" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PgRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PgRangeBound a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PgRangeBound a)))) |
data PgRangeBound a Source #
Represents a single bound on a Range. A bound always has a type, but may not have a value (the absense of a value represents unbounded).
Constructors
PgRangeBound PgBoundType (Maybe a) |
Instances
Generic (PgRangeBound a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Associated Types
Methods from :: PgRangeBound a -> Rep (PgRangeBound a) x # to :: Rep (PgRangeBound a) x -> PgRangeBound a # | |||||
Show a => Show (PgRangeBound a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods showsPrec :: Int -> PgRangeBound a -> ShowS # show :: PgRangeBound a -> String # showList :: [PgRangeBound a] -> ShowS # | |||||
Eq a => Eq (PgRangeBound a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific Methods (==) :: PgRangeBound a -> PgRangeBound a -> Bool # (/=) :: PgRangeBound a -> PgRangeBound a -> Bool # | |||||
Hashable a => Hashable (PgRangeBound a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific | |||||
type Rep (PgRangeBound a) Source # | |||||
Defined in Database.Beam.Postgres.PgSpecific type Rep (PgRangeBound a) = D1 ('MetaData "PgRangeBound" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-9RY3FTbcpgg9tLiPshayrX" 'False) (C1 ('MetaCons "PgRangeBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PgBoundType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)))) |
class PgIsRange (n :: k) where Source #
A class representing Postgres Range types and how to refer to them when speaking to the database.
For custom Range types, create an uninhabited type, and make it an instance of this class.
Instances
PgIsRange PgDateRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
PgIsRange PgInt4Range Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
PgIsRange PgInt8Range Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
PgIsRange PgNumRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
PgIsRange PgTsRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
PgIsRange PgTsTzRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
data PgInt4Range Source #
Instances
PgIsRange PgInt4Range Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
data PgInt8Range Source #
Instances
PgIsRange PgInt8Range Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
data PgNumRange Source #
Instances
PgIsRange PgNumRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
Instances
PgIsRange PgTsRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
data PgTsTzRange Source #
Instances
PgIsRange PgTsTzRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
data PgDateRange Source #
Instances
PgIsRange PgDateRange Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods |
inclusive :: a -> PgRangeBound a Source #
unbounded :: PgRangeBound a Source #
(-@>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-@>) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s a -> QGenExpr context Postgres s Bool Source #
(-<@-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(<@-) :: QGenExpr context Postgres s a -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-&&-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-<<-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(->>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-&<-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-&>-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(--|--) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #
(-+-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) Source #
(-*-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) Source #
(-.-) :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) Source #
The postgres range operator -
.
rLower_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (Maybe a) Source #
rUpper_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (Maybe a) Source #
rangeMerge_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s (PgRange n a) Source #
century_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
decade_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
dow_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
doy_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
epoch_ :: HasSqlTime tgt => ExtractField Postgres tgt NominalDiffTime Source #
isodow_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
isoyear_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
microseconds_ :: HasSqlTime tgt => ExtractField Postgres tgt Int32 Source #
milliseconds_ :: HasSqlTime tgt => ExtractField Postgres tgt Int32 Source #
millennium_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
quarter_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
week_ :: HasSqlDate tgt => ExtractField Postgres tgt Int32 Source #
pgBoolOr :: QExpr Postgres s a -> QAgg Postgres s (Maybe Bool) Source #
Postgres bool_or
aggregate. Returns true if any of the rows are true.
pgBoolAnd :: QExpr Postgres s a -> QAgg Postgres s (Maybe Bool) Source #
Postgres bool_and
aggregate. Returns false unless every row is true.
pgStringAgg :: BeamSqlBackendIsString Postgres str => QExpr Postgres s str -> QExpr Postgres s str -> QAgg Postgres s (Maybe str) Source #
Joins the string value in each row of the first argument, using the second
argument as a delimiter. See pgStringAggOver
if you want to provide
explicit quantification.
pgStringAggOver :: BeamSqlBackendIsString Postgres str => Maybe PgAggregationSetQuantifierSyntax -> QExpr Postgres s str -> QExpr Postgres s str -> QAgg Postgres s (Maybe str) Source #
The Postgres string_agg
function, with an explicit quantifier. Joins the
values of the second argument using the delimiter given by the third.
pgNubBy_ :: forall key r (db :: (Type -> Type) -> Type) s. (Projectible Postgres key, Projectible Postgres r) => (r -> key) -> Q Postgres db s r -> Q Postgres db s r Source #
Modify a query to only return rows where the supplied key function returns
a unique value. This corresponds to the Postgres DISTINCT ON
support.
ilike_ :: BeamSqlBackendIsString Postgres text => QExpr Postgres s text -> QExpr Postgres s text -> QExpr Postgres s Bool Source #
Postgres ILIKE
operator. A case-insensitive version of like_
.
ilike_' :: (BeamSqlBackendIsString Postgres left, BeamSqlBackendIsString Postgres right) => QExpr Postgres s left -> QExpr Postgres s right -> QExpr Postgres s Bool Source #
Postgres ILIKE
operator. A case-insensitive version of like_'
.
Postgres extension support
data PgExtensionEntity extension Source #
Represents an extension in a database.
For example, to include the Database.Beam.Postgres.PgCrypto extension in a database,
import Database.Beam.Postgres.PgCrypto data MyDatabase entity = MyDatabase { _table1 :: entity (TableEntity Table1) , _cryptoExtension :: entity (PgExtensionEntity PgCrypto) } migratableDbSettings :: CheckedDatabaseSettings Postgres MyDatabase migratableDbSettings = defaultMigratableDbSettings dbSettings :: DatabaseSettings Postgres MyDatabase dbSettings = unCheckDatabase migratableDbSettings
Note that our database now only works in the Postgres
backend.
Extensions are implemented as records of functions and values that expose
extension functionality. For example, the pgcrypto
extension (implemented
by PgCrypto
) provides cryptographic functions. Thus, PgCrypto
is a record
of functions over QGenExpr
which wrap the underlying postgres
functionality.
You get access to these functions by retrieving them from the entity in the database.
For example, to use the pgcrypto
extension in the database above:
let PgCrypto { pgCryptoDigestText = digestText , pgCryptoCrypt = crypt } = getPgExtension (_cryptoExtension dbSettings) in fmap_ (tbl -> (tbl, crypt (_field1 tbl) (_salt tbl))) (all_ (table1 dbSettings))
To implement your own extension, create a record type, and implement the
IsPgExtension
type class.
Instances
IsDatabaseEntity Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions Associated Types
Methods dbEntityName :: Lens' (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) Text # dbEntitySchema :: Traversal' (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) (Maybe Text) # dbEntityAuto :: Text -> DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) # | |||||||||||||
IsCheckedDatabaseEntity Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions Associated Types
Methods unCheck :: CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) # unChecked :: Lens' (CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) # collectEntityChecks :: CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> [SomeDatabasePredicate] # checkedDbEntityAuto :: Text -> CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) # | |||||||||||||
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e))) Source # | There are no fields to rename when defining entities | ||||||||||||
Defined in Database.Beam.Postgres.Extensions Methods renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e)) # | |||||||||||||
type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension | |||||||||||||
data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) where
| |||||||||||||
type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension | |||||||||||||
type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) | |||||||||||||
newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # | |||||||||||||
Defined in Database.Beam.Postgres.Extensions newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) = CheckedPgExtension (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) |
class IsPgExtension extension where Source #
Type class implemented by any Postgresql extension
Methods
pgExtensionName :: Proxy extension -> Text Source #
Return the name of this extension. This should be the string that is
passed to CREATE EXTENSION
. For example, PgCrypto
returns "pgcrypto"
.
pgExtensionBuild :: extension Source #
Return a value of this extension type. This should fill in all fields in
the record. For example, PgCrypto
builds a record where each function
wraps the underlying Postgres one.
Instances
pgCreateExtension :: forall extension (db :: (Type -> Type) -> Type). IsPgExtension extension => Migration Postgres (CheckedDatabaseEntity Postgres db (PgExtensionEntity extension)) Source #
Migration
representing the Postgres CREATE EXTENSION
command. Because
the extension name is statically known by the extension type and
IsPgExtension
type class, this simply produces the checked extension
entity.
If you need to use the extension in subsequent migration steps, use
getPgExtension
and unCheck
to get access to the underlying
DatabaseEntity
.
pgDropExtension :: CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) -> Migration Postgres () Source #
Migration
representing the Postgres DROP EXTENSION
. After this
executes, you should expect any further uses of the extension to fail.
Unfortunately, without linear types, we cannot check this.
getPgExtension :: forall (db :: (Type -> Type) -> Type) extension. DatabaseEntity Postgres db (PgExtensionEntity extension) -> extension Source #
Get the extension record from a database entity. See the documentation for
PgExtensionEntity
.
Utilities for defining custom instances
fromPgIntegral :: (FromField a, Integral a, Typeable a) => FromBackendRowM Postgres a Source #
Deserialize integral fields, possibly downcasting from a larger integral type, but only if we won't lose data
fromPgScientificOrIntegral :: (Bounded a, Integral a) => FromBackendRowM Postgres a Source #
Deserialize integral fields, possibly downcasting from a larger numeric type
via Scientific
if we won't lose data, and then falling back to any integral
type via Integer
Debug support
class PgDebugStmt statement Source #
Type class for Sql*
types that can be turned into Postgres
syntax, for use in the following debugging functions
These include
Minimal complete definition
pgStmtSyntax
Instances
PgDebugStmt (PgDeleteReturning a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: PgDeleteReturning a -> Maybe PgSyntax | |
PgDebugStmt (PgInsertReturning a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: PgInsertReturning a -> Maybe PgSyntax | |
PgDebugStmt (PgUpdateReturning a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: PgUpdateReturning a -> Maybe PgSyntax | |
PgDebugStmt (SqlDelete Postgres a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: SqlDelete Postgres a -> Maybe PgSyntax | |
PgDebugStmt (SqlInsert Postgres a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: SqlInsert Postgres a -> Maybe PgSyntax | |
PgDebugStmt (SqlSelect Postgres a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: SqlSelect Postgres a -> Maybe PgSyntax | |
PgDebugStmt (SqlUpdate Postgres a) Source # | |
Defined in Database.Beam.Postgres.Debug Methods pgStmtSyntax :: SqlUpdate Postgres a -> Maybe PgSyntax |
pgTraceStmtIO :: PgDebugStmt statement => Connection -> statement -> IO () Source #
pgTraceStmtIO' :: PgDebugStmt statement => Connection -> statement -> IO ByteString Source #
pgTraceStmt :: PgDebugStmt statement => statement -> Pg () Source #
postgresql-simple
re-exports
data ResultError #
Exception thrown if conversion from a SQL value to a Haskell value fails.
Constructors
Incompatible | The SQL and Haskell types are not compatible. |
Fields
| |
UnexpectedNull | A SQL |
Fields
| |
ConversionFailed | The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row). |
Fields
|
Instances
Exception ResultError | |
Defined in Database.PostgreSQL.Simple.FromField Methods toException :: ResultError -> SomeException # fromException :: SomeException -> Maybe ResultError # displayException :: ResultError -> String # | |
Show ResultError | |
Defined in Database.PostgreSQL.Simple.FromField Methods showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS # | |
Eq ResultError | |
Defined in Database.PostgreSQL.Simple.FromField |
Constructors
SqlError | |
Fields |
Instances
Exception SqlError | |
Defined in Database.PostgreSQL.Simple.Internal Methods toException :: SqlError -> SomeException # fromException :: SomeException -> Maybe SqlError # displayException :: SqlError -> String # | |
Show SqlError | |
Eq SqlError | |
data Connection #
Instances
Eq Connection | |
Defined in Database.PostgreSQL.Simple.Internal |
data ConnectInfo #
Constructors
ConnectInfo | |
Fields
|
Instances
Generic ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal Associated Types
| |||||
Read ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal Methods readsPrec :: Int -> ReadS ConnectInfo # readList :: ReadS [ConnectInfo] # readPrec :: ReadPrec ConnectInfo # readListPrec :: ReadPrec [ConnectInfo] # | |||||
Show ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal Methods showsPrec :: Int -> ConnectInfo -> ShowS # show :: ConnectInfo -> String # showList :: [ConnectInfo] -> ShowS # | |||||
Eq ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal | |||||
type Rep ConnectInfo | |||||
Defined in Database.PostgreSQL.Simple.Internal type Rep ConnectInfo = D1 ('MetaData "ConnectInfo" "Database.PostgreSQL.Simple.Internal" "postgresql-simple-0.7.0.0-Dw629zQ2oNI25ydklaDe9" 'False) (C1 ('MetaCons "ConnectInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "connectHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "connectPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "connectUser") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "connectPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "connectDatabase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
defaultConnectInfo :: ConnectInfo #
Default information for setting up a connection.
Defaults are as follows:
- Server on
localhost
- Port on
5432
- User
postgres
- No password
- Database
postgres
Use as in the following example:
connect defaultConnectInfo { connectHost = "db.example.com" }
connectPostgreSQL :: ByteString -> IO Connection #
Attempt to make a connection based on a libpq connection string. See https://www.postgresql.org/docs/9.5/static/libpq-connect.html#LIBPQ-CONNSTRING for more information. Also note that environment variables also affect parameters not provided, parameters provided as the empty string, and a few other things; see https://www.postgresql.org/docs/9.5/static/libpq-envars.html for details. Here is an example with some of the most commonly used parameters:
host='db.somedomain.com' port=5432 ...
This attempts to connect to db.somedomain.com:5432
. Omitting the port
will normally default to 5432.
On systems that provide unix domain sockets, omitting the host parameter
will cause libpq to attempt to connect via unix domain sockets.
The default filesystem path to the socket is constructed from the
port number and the DEFAULT_PGSOCKET_DIR
constant defined in the
pg_config_manual.h
header file. Connecting via unix sockets tends
to use the peer
authentication method, which is very secure and
does not require a password.
On Windows and other systems without unix domain sockets, omitting
the host will default to localhost
.
... dbname='postgres' user='postgres' password='secret \' \\ pw'
This attempts to connect to a database named postgres
with
user postgres
and password secret ' \ pw
. Backslash
characters will have to be double-quoted in literal Haskell strings,
of course. Omitting dbname
and user
will both default to the
system username that the client process is running as.
Omitting password
will default to an appropriate password found
in the pgpass
file, or no password at all if a matching line is
not found. The path of the pgpass
file may be specified by setting
the PGPASSFILE
environment variable. See
https://www.postgresql.org/docs/9.5/static/libpq-pgpass.html for
more information regarding this file.
As all parameters are optional and the defaults are sensible, the empty connection string can be useful for development and exploratory use, assuming your system is set up appropriately.
On Unix, such a setup would typically consist of a local postgresql server listening on port 5432, as well as a system user, database user, and database sharing a common name, with permissions granted to the user on the database.
On Windows, in addition you will either need pg_hba.conf
to specify the use of the trust
authentication method for
the connection, which may not be appropriate for multiuser
or production machines, or you will need to use a pgpass
file
with the password
or md5
authentication methods.
See https://www.postgresql.org/docs/9.5/static/client-authentication.html for more information regarding the authentication process.
SSL/TLS will typically "just work" if your postgresql server supports or
requires it. However, note that libpq is trivially vulnerable to a MITM
attack without setting additional SSL connection parameters. In
particular, sslmode
needs to be set to require
, verify-ca
, or
verify-full
in order to perform certificate validation. When sslmode
is require
, then you will also need to specify a sslrootcert
file,
otherwise no validation of the server's identity will be performed.
Client authentication via certificates is also possible via the
sslcert
and sslkey
parameters. See
https://www.postgresql.org/docs/9.5/static/libpq-ssl.html
for detailed information regarding libpq and SSL.
connect :: ConnectInfo -> IO Connection #
Connect with the given username to the given database. Will throw an exception if it cannot connect.
close :: Connection -> IO () #