beam-postgres
Safe HaskellNone
LanguageHaskell2010

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 ARRAYs, RANGEs, 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

Beam Postgres backend

data Postgres Source #

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

Instances details
BeamSqlBackend Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

BeamHasInsertOnConflict Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Full

Associated Types

newtype SqlConflictTarget Postgres table 
Instance details

Defined in Database.Beam.Postgres.Full

newtype SqlConflictAction Postgres table 
Instance details

Defined in Database.Beam.Postgres.Full

newtype SqlConflictAction Postgres table = PgConflictAction (table (QField QInternal) -> PgConflictActionSyntax)

Methods

insertOnConflict :: forall table (db :: (Type -> Type) -> Type) s. Beamable table => DatabaseEntity Postgres db (TableEntity table) -> SqlInsertValues Postgres (table (QExpr Postgres s)) -> SqlConflictTarget Postgres table -> SqlConflictAction Postgres table -> SqlInsert Postgres table #

anyConflict :: forall (table :: (Type -> Type) -> Type). SqlConflictTarget Postgres table #

conflictingFields :: Projectible Postgres proj => (table (QExpr Postgres QInternal) -> proj) -> SqlConflictTarget Postgres table #

conflictingFieldsWhere :: Projectible Postgres proj => (table (QExpr Postgres QInternal) -> proj) -> (forall s. table (QExpr Postgres s) -> QExpr Postgres s Bool) -> SqlConflictTarget Postgres table #

onConflictDoNothing :: forall (table :: (Type -> Type) -> Type). SqlConflictAction Postgres table #

onConflictUpdateSet :: Beamable table => (forall s. table (QField s) -> table (QExpr Postgres s) -> QAssignment Postgres s) -> SqlConflictAction Postgres table #

onConflictUpdateSetWhere :: Beamable table => (forall s. table (QField s) -> table (QExpr Postgres s) -> QAssignment Postgres s) -> (forall s. table (QField s) -> table (QExpr Postgres s) -> QExpr Postgres s Bool) -> SqlConflictAction Postgres table #

BeamBackend Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Associated Types

type BackendFromField Postgres 
Instance details

Defined in Database.Beam.Postgres.Types

type BackendFromField Postgres = FromField
HasSqlInTable Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

inRowValuesE :: Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> [BeamSqlBackendExpressionSyntax Postgres] -> BeamSqlBackendExpressionSyntax Postgres

HasQBuilder Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

buildSqlQuery :: forall a (db :: (Type -> Type) -> Type) s. Projectible Postgres a => TablePrefix -> Q Postgres db s a -> BeamSqlBackendSelectSyntax Postgres

BeamSqlBackendHasSerial Postgres 
Instance details

Defined in Database.Beam.Postgres.Migrate

Methods

genericSerial :: FieldReturnType 'True 'False Postgres (SqlSerial Int) a => Text -> a

BeamMigrateOnlySqlBackend Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

MonadBeam Postgres Pg 
Instance details

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 
Instance details

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 
Instance details

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 
Instance details

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]

FromBackendRow Postgres Value Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres SqlNull Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres SqlNull

valuesNeeded :: Proxy Postgres -> Proxy SqlNull -> Int

FromBackendRow Postgres PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Int16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Int32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Int64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Word16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Word32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Word64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Oid Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Oid

valuesNeeded :: Proxy Postgres -> Proxy Oid -> Int

FromBackendRow Postgres HStoreList Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres HStoreMap Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Date Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Date

valuesNeeded :: Proxy Postgres -> Proxy Date -> Int

FromBackendRow Postgres LocalTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres UTCTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres ZonedTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Null Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Null

valuesNeeded :: Proxy Postgres -> Proxy Null -> Int

FromBackendRow Postgres Scientific Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Text

valuesNeeded :: Proxy Postgres -> Proxy Text -> Int

FromBackendRow Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Text

valuesNeeded :: Proxy Postgres -> Proxy Text -> Int

FromBackendRow Postgres Day Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Day

valuesNeeded :: Proxy Postgres -> Proxy Day -> Int

FromBackendRow Postgres UTCTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres LocalTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres TimeOfDay Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres UUID Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres UUID

valuesNeeded :: Proxy Postgres -> Proxy UUID -> Int

FromBackendRow Postgres Integer Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Bool Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Bool

valuesNeeded :: Proxy Postgres -> Proxy Bool -> Int

FromBackendRow Postgres Char Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Char

valuesNeeded :: Proxy Postgres -> Proxy Char -> Int

FromBackendRow Postgres Double Source # 
Instance details

Defined in Database.Beam.Postgres.Types

(TypeError (PreferExplicitSize Int Int32) :: Constraint) => FromBackendRow Postgres Int Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Int

valuesNeeded :: Proxy Postgres -> Proxy Int -> Int

(TypeError (PreferExplicitSize Word Word32) :: Constraint) => FromBackendRow Postgres Word Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres Word

valuesNeeded :: Proxy Postgres -> Proxy Word -> Int

HasSqlEqualityCheck Postgres Value Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Value -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Value -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Value -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Value -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres PgMoney 
Instance details

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

HasSqlEqualityCheck Postgres TsQuery 
Instance details

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

HasSqlEqualityCheck Postgres TsVector 
Instance details

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

HasSqlEqualityCheck Postgres TsVectorConfig 
Instance details

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

HasSqlEqualityCheck Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy ByteString -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Int16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Int16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Int16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Int16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Int16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Int32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Int32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Int32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Int32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Int32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Int64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Int64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Int64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Int64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Int64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Int8 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Int8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Int8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Int8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Int8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Word16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Word16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Word16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Word16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Word16 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Word32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Word32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Word32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Word32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Word32 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Word64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Word64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Word64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Word64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Word64 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Word8 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Word8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Word8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Word8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Word8 -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Oid Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Oid -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Oid -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Oid -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Oid -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres HStoreList Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy HStoreList -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy HStoreList -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy HStoreList -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy HStoreList -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres HStoreMap Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy HStoreMap -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy HStoreMap -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy HStoreMap -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy HStoreMap -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Date Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Date -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Date -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Date -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Date -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres LocalTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy LocalTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy LocalTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy LocalTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy LocalTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres UTCTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy UTCTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy UTCTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy UTCTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy UTCTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres ZonedTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy ZonedTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy ZonedTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy ZonedTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy ZonedTimestamp -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Scientific Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Scientific -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Scientific -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Scientific -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Scientific -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Text -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Day Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Day -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Day -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Day -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Day -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres NominalDiffTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy NominalDiffTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy NominalDiffTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy NominalDiffTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy NominalDiffTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres UTCTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy UTCTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy UTCTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy UTCTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy UTCTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres LocalTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy LocalTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy LocalTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy LocalTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy LocalTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres TimeOfDay Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy TimeOfDay -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy TimeOfDay -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy TimeOfDay -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy TimeOfDay -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres ZonedTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy ZonedTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy ZonedTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy ZonedTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy ZonedTime -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres UUID Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy UUID -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy UUID -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy UUID -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy UUID -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Integer Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Integer -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Integer -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Integer -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Integer -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Bool Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Bool -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Bool -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Bool -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Bool -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Double Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Double -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Double -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Double -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Double -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres Float Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Float -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Float -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Float -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Float -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasSqlEqualityCheck Postgres Int Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Int -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Int -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Int -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Int -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

(TypeError (PreferExplicitSize Word Word32) :: Constraint) => HasSqlEqualityCheck Postgres Word Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy Word -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy Word -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy Word -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy Word -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Value Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Value -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Value -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres PgMoney 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres TsQuery 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres TsVector 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres TsVectorConfig 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy ByteString -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy ByteString -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy ByteString -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy ByteString -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Int16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Int16 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Int16 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Int32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Int32 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Int32 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Int64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Int64 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Int64 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Int8 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Int8 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Int8 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Word16 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Word16 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Word16 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Word32 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Word32 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Word32 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Word64 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Word64 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Word64 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Word8 Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Word8 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Word8 -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Oid Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Oid -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Oid -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres HStoreList Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy HStoreList -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy HStoreList -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres HStoreMap Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy HStoreMap -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy HStoreMap -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Date Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Date -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Date -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres LocalTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy LocalTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy LocalTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres UTCTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy UTCTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy UTCTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres ZonedTimestamp Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy ZonedTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy ZonedTimestamp -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Scientific Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Scientific -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Scientific -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Text -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Text -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Text -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Text -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Day Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Day -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Day -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres NominalDiffTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy NominalDiffTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy NominalDiffTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres UTCTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy UTCTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy UTCTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres LocalTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy LocalTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy LocalTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres TimeOfDay Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy TimeOfDay -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy TimeOfDay -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres ZonedTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy ZonedTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy ZonedTime -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres UUID Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy UUID -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy UUID -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Integer Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Integer -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Integer -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Bool Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Bool -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Bool -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Double Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Double -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Double -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres Float Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Float -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Float -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasSqlQuantifiedEqualityCheck Postgres Int Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Int -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Int -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

(TypeError (PreferExplicitSize Word Word32) :: Constraint) => HasSqlQuantifiedEqualityCheck Postgres Word Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy Word -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy Word -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasDefaultSqlDataType Postgres PgBox 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgBox -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgBox -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres PgLine 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgLine -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgLine -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres PgLineSegment 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgLineSegment -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgLineSegment -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres PgMoney 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgMoney -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgMoney -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres PgPoint 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgPoint -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgPoint -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres TsQuery 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy TsQuery -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy TsQuery -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres TsVector 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy TsVector -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy TsVector -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres ByteString Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy ByteString -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy ByteString -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres UTCTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy UTCTime -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy UTCTime -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres LocalTime Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy LocalTime -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy LocalTime -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres UUID Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy UUID -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy UUID -> Proxy Postgres -> Bool -> [FieldCheck]

BeamSqlBackendIsString Postgres Text Source # 
Instance details

Defined in Database.Beam.Postgres.Types

BeamSqlBackendIsString Postgres String Source # 
Instance details

Defined in Database.Beam.Postgres.Types

(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

fromBackendRow :: FromBackendRowM Postgres (PgJSON a)

valuesNeeded :: Proxy Postgres -> Proxy (PgJSON a) -> Int

(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

fromBackendRow :: FromBackendRowM Postgres (PgJSONB a)

valuesNeeded :: Proxy Postgres -> Proxy (PgJSONB a) -> Int

FromBackendRow Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (CI Text)

valuesNeeded :: Proxy Postgres -> Proxy (CI Text) -> Int

FromBackendRow Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (CI Text)

valuesNeeded :: Proxy Postgres -> Proxy (CI Text) -> Int

FromBackendRow Postgres (Ratio Integer) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

(FromField a, Typeable a) => FromBackendRow Postgres (PGRange a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (PGRange a)

valuesNeeded :: Proxy Postgres -> Proxy (PGRange a) -> Int

FromBackendRow Postgres (Binary ByteString) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres (Binary ByteString) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

(FromField a, Typeable a) => FromBackendRow Postgres (PGArray a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (PGArray a)

valuesNeeded :: Proxy Postgres -> Proxy (PGArray a) -> Int

(FromField a, Typeable a) => FromBackendRow Postgres (Vector a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (Vector a)

valuesNeeded :: Proxy Postgres -> Proxy (Vector a) -> Int

FromBackendRow Postgres [Char] Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres [Char]

valuesNeeded :: Proxy Postgres -> Proxy [Char] -> Int

HasSqlEqualityCheck Postgres (PgJSON a) 
Instance details

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

HasSqlEqualityCheck Postgres (PgJSONB a) 
Instance details

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

HasSqlEqualityCheck Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy (CI Text) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres (Vector a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy (Vector a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy (Vector a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy (Vector a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy (Vector a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlEqualityCheck Postgres [Char] Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy [Char] -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy [Char] -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy [Char] -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy [Char] -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres (PgJSON a) 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres (PgJSONB a) 
Instance details

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

HasSqlQuantifiedEqualityCheck Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy (CI Text) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy (CI Text) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres (CI Text) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy (CI Text) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy (CI Text) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres (Vector a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy (Vector a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy (Vector a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres [Char] Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy [Char] -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy [Char] -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

IsDatabaseEntity Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

Associated Types

data DatabaseEntityDescriptor Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

data DatabaseEntityDescriptor Postgres (PgType a) where
type DatabaseEntityDefaultRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type DatabaseEntityDefaultRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a, IsPgCustomDataType a)
type DatabaseEntityRegularRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type DatabaseEntityRegularRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a)

Methods

dbEntityName :: Lens' (DatabaseEntityDescriptor Postgres (PgType a)) Text

dbEntitySchema :: Traversal' (DatabaseEntityDescriptor Postgres (PgType a)) (Maybe Text)

dbEntityAuto :: Text -> DatabaseEntityDescriptor Postgres (PgType a)

IsDatabaseEntity Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

Associated Types

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) where
type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension

Methods

dbEntityName :: Lens' (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) Text

dbEntitySchema :: Traversal' (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)) (Maybe Text)

dbEntityAuto :: Text -> DatabaseEntityDescriptor Postgres (PgExtensionEntity extension)

HasDefaultSqlDataType Postgres (SqlSerial Int16) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy (SqlSerial Int16) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (SqlSerial Int16) -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres (SqlSerial Int32) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy (SqlSerial Int32) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (SqlSerial Int32) -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres (SqlSerial Int64) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy (SqlSerial Int64) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (SqlSerial Int64) -> Proxy Postgres -> Bool -> [FieldCheck]

(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasDefaultSqlDataType Postgres (SqlSerial Int) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

defaultSqlDataType :: Proxy (SqlSerial Int) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (SqlSerial Int) -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres (PgJSON a) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy (PgJSON a) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (PgJSON a) -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres (PgJSONB a) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy (PgJSONB a) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (PgJSONB a) -> Proxy Postgres -> Bool -> [FieldCheck]

HasDefaultSqlDataType Postgres a => HasDefaultSqlDataType Postgres (Vector a) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy (Vector a) -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy (Vector a) -> Proxy Postgres -> Bool -> [FieldCheck]

IsCheckedDatabaseEntity Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

Associated Types

data CheckedDatabaseEntityDescriptor Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

data CheckedDatabaseEntityDescriptor Postgres (PgType a) where
type CheckedDatabaseEntityDefaultRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type CheckedDatabaseEntityDefaultRequirements Postgres (PgType a) = DatabaseEntityDefaultRequirements Postgres (PgType a)

Methods

unCheck :: CheckedDatabaseEntityDescriptor Postgres (PgType a) -> DatabaseEntityDescriptor Postgres (PgType a)

unChecked :: Lens' (CheckedDatabaseEntityDescriptor Postgres (PgType a)) (DatabaseEntityDescriptor Postgres (PgType a))

collectEntityChecks :: CheckedDatabaseEntityDescriptor Postgres (PgType a) -> [SomeDatabasePredicate]

checkedDbEntityAuto :: Text -> CheckedDatabaseEntityDescriptor Postgres (PgType a)

IsCheckedDatabaseEntity Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

Associated Types

newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) = CheckedPgExtension (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension))
type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension)

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)

(FromField a, Typeable a, Typeable n, Ord a) => FromBackendRow Postgres (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

fromBackendRow :: FromBackendRowM Postgres (PgRange n a)

valuesNeeded :: Proxy Postgres -> Proxy (PgRange n a) -> Int

(FromField a, FromField b, Typeable a, Typeable b) => FromBackendRow Postgres (Either a b) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

fromBackendRow :: FromBackendRowM Postgres (Either a b)

valuesNeeded :: Proxy Postgres -> Proxy (Either a b) -> Int

HasSqlEqualityCheck Postgres (PgRange n a) 
Instance details

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) 
Instance details

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

HasSqlEqualityCheck Postgres a => HasSqlEqualityCheck Postgres (Tagged t a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlEqE :: Proxy (Tagged t a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqE :: Proxy (Tagged t a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlEqTriE :: Proxy (Tagged t a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlNeqTriE :: Proxy (Tagged t a) -> Proxy Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

HasSqlQuantifiedEqualityCheck Postgres a => HasSqlQuantifiedEqualityCheck Postgres (Tagged t a) Source # 
Instance details

Defined in Database.Beam.Postgres.Types

Methods

sqlQEqE :: Proxy (Tagged t a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

sqlQNeqE :: Proxy (Tagged t a) -> Proxy Postgres -> Maybe (BeamSqlBackendExpressionQuantifierSyntax Postgres) -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres -> BeamSqlBackendExpressionSyntax Postgres

RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor Postgres (PgType a))) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

Methods

renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor Postgres (PgType a))

RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e)))

There are no fields to rename when defining entities

Instance details

Defined in Database.Beam.Postgres.Extensions

Methods

renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e))

PgDebugStmt (SqlDelete Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlDelete Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlInsert Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlInsert Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlSelect Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlSelect Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlUpdate Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlUpdate Postgres a -> Maybe PgSyntax

type BeamSqlBackendSyntax Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

type BeamSqlBackendSyntax Postgres = PgCommandSyntax
newtype SqlConflictAction Postgres table Source # 
Instance details

Defined in Database.Beam.Postgres.Full

newtype SqlConflictAction Postgres table = PgConflictAction (table (QField QInternal) -> PgConflictActionSyntax)
newtype SqlConflictTarget Postgres table Source # 
Instance details

Defined in Database.Beam.Postgres.Full

type BackendFromField Postgres Source # 
Instance details

Defined in Database.Beam.Postgres.Types

type BackendFromField Postgres = FromField
type DatabaseEntityDefaultRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type DatabaseEntityDefaultRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a, IsPgCustomDataType a)
type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
data DatabaseEntityDescriptor Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

data DatabaseEntityDescriptor Postgres (PgType a) where
data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) where
type DatabaseEntityRegularRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type DatabaseEntityRegularRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a)
type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
type CheckedDatabaseEntityDefaultRequirements Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

type CheckedDatabaseEntityDefaultRequirements Postgres (PgType a) = DatabaseEntityDefaultRequirements Postgres (PgType a)
type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension)
data CheckedDatabaseEntityDescriptor Postgres (PgType a) 
Instance details

Defined in Database.Beam.Postgres.CustomTypes

data CheckedDatabaseEntityDescriptor Postgres (PgType a) where
newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) = CheckedPgExtension (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension))

data Pg a Source #

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

Instances details
MonadIO Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

liftIO :: IO a -> Pg a #

Applicative Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

pure :: a -> Pg a #

(<*>) :: Pg (a -> b) -> Pg a -> Pg b #

liftA2 :: (a -> b -> c) -> Pg a -> Pg b -> Pg c #

(*>) :: Pg a -> Pg b -> Pg b #

(<*) :: Pg a -> Pg b -> Pg a #

Functor Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

fmap :: (a -> b) -> Pg a -> Pg b #

(<$) :: a -> Pg b -> Pg a #

Monad Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

(>>=) :: Pg a -> (a -> Pg b) -> Pg b #

(>>) :: Pg a -> Pg b -> Pg b #

return :: a -> Pg a #

MonadFail Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

fail :: String -> Pg a #

MonadBeam Postgres Pg Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.Connection

Associated Types

type StM Pg a 
Instance details

Defined in Database.Beam.Postgres.Connection

type StM Pg a = a

Methods

liftBaseWith :: (RunInBase Pg IO -> IO a) -> Pg a #

restoreM :: StM Pg a -> Pg a #

MonadBase IO Pg Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

Methods

liftBase :: IO α -> Pg α #

type StM Pg a Source # 
Instance details

Defined in Database.Beam.Postgres.Connection

type StM Pg a = a

Executing actions against the backend

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

Instances details
IsSql92Syntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92SelectSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectSyntax PgCommandSyntax = PgSelectSyntax
type Sql92InsertSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertSyntax PgCommandSyntax = PgInsertSyntax
type Sql92UpdateSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateSyntax PgCommandSyntax = PgUpdateSyntax
type Sql92DeleteSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteSyntax PgCommandSyntax = PgDeleteSyntax

Methods

selectCmd :: Sql92SelectSyntax PgCommandSyntax -> PgCommandSyntax

insertCmd :: Sql92InsertSyntax PgCommandSyntax -> PgCommandSyntax

updateCmd :: Sql92UpdateSyntax PgCommandSyntax -> PgCommandSyntax

deleteCmd :: Sql92DeleteSyntax PgCommandSyntax -> PgCommandSyntax

IsSql92DdlCommandSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92DdlCommandCreateTableSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandCreateTableSyntax PgCommandSyntax = PgCreateTableSyntax
type Sql92DdlCommandAlterTableSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandAlterTableSyntax PgCommandSyntax = PgAlterTableSyntax
type Sql92DdlCommandDropTableSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandDropTableSyntax PgCommandSyntax

Methods

createTableCmd :: Sql92DdlCommandCreateTableSyntax PgCommandSyntax -> PgCommandSyntax

dropTableCmd :: Sql92DdlCommandDropTableSyntax PgCommandSyntax -> PgCommandSyntax

alterTableCmd :: Sql92DdlCommandAlterTableSyntax PgCommandSyntax -> PgCommandSyntax

IsSql92DdlSchemaCommandSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax
type Sql92DdlCommandDropSchemaSyntax PgCommandSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandDropSchemaSyntax PgCommandSyntax

Methods

createSchemaCmd :: Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax -> PgCommandSyntax

dropSchemaCmd :: Sql92DdlCommandDropSchemaSyntax PgCommandSyntax -> PgCommandSyntax

type Sql92DeleteSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteSyntax PgCommandSyntax = PgDeleteSyntax
type Sql92InsertSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertSyntax PgCommandSyntax = PgInsertSyntax
type Sql92SelectSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectSyntax PgCommandSyntax = PgSelectSyntax
type Sql92UpdateSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateSyntax PgCommandSyntax = PgUpdateSyntax
type Sql92DdlCommandAlterTableSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandAlterTableSyntax PgCommandSyntax = PgAlterTableSyntax
type Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandCreateSchemaSyntax PgCommandSyntax
type Sql92DdlCommandCreateTableSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandCreateTableSyntax PgCommandSyntax = PgCreateTableSyntax
type Sql92DdlCommandDropSchemaSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandDropSchemaSyntax PgCommandSyntax
type Sql92DdlCommandDropTableSyntax PgCommandSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DdlCommandDropTableSyntax PgCommandSyntax

data PgSyntax 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.

Instances

Instances details
Sql92DisplaySyntax PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Monoid PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Semigroup PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Show PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Eq PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Hashable PgSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Methods

hashWithSalt :: Int -> PgSyntax -> Int #

hash :: PgSyntax -> Int #

data PgSelectSyntax Source #

IsSql92SelectSyntax for Postgres

Instances

Instances details
IsSql92SelectSyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92SelectSelectTableSyntax PgSelectSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectSelectTableSyntax PgSelectSyntax
type Sql92SelectOrderingSyntax PgSelectSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectOrderingSyntax PgSelectSyntax = PgOrderingSyntax

Methods

selectStmt :: Sql92SelectSelectTableSyntax PgSelectSyntax -> [Sql92SelectOrderingSyntax PgSelectSyntax] -> Maybe Integer -> Maybe Integer -> PgSelectSyntax

IsSql99CommonTableExpressionSelectSyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql99SelectCTESyntax PgSelectSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql99SelectCTESyntax PgSelectSyntax

Methods

withSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax

IsSql99RecursiveCommonTableExpressionSelectSyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Methods

withRecursiveSyntax :: [Sql99SelectCTESyntax PgSelectSyntax] -> PgSelectSyntax -> PgSelectSyntax

type Sql92SelectOrderingSyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectOrderingSyntax PgSelectSyntax = PgOrderingSyntax
type Sql92SelectSelectTableSyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92SelectSelectTableSyntax PgSelectSyntax
type Sql99SelectCTESyntax PgSelectSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql99SelectCTESyntax PgSelectSyntax

data PgInsertSyntax Source #

IsSql92InsertSyntax for Postgres

Instances

Instances details
IsSql92InsertSyntax PgInsertSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92InsertValuesSyntax PgInsertSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertValuesSyntax PgInsertSyntax = PgInsertValuesSyntax
type Sql92InsertTableNameSyntax PgInsertSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertTableNameSyntax PgInsertSyntax = PgTableNameSyntax

Methods

insertStmt :: Sql92InsertTableNameSyntax PgInsertSyntax -> [Text] -> Sql92InsertValuesSyntax PgInsertSyntax -> PgInsertSyntax

type Sql92InsertTableNameSyntax PgInsertSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertTableNameSyntax PgInsertSyntax = PgTableNameSyntax
type Sql92InsertValuesSyntax PgInsertSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92InsertValuesSyntax PgInsertSyntax = PgInsertValuesSyntax

data PgUpdateSyntax Source #

IsSql92UpdateSyntax for Postgres

Instances

Instances details
IsSql92UpdateSyntax PgUpdateSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92UpdateTableNameSyntax PgUpdateSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateTableNameSyntax PgUpdateSyntax = PgTableNameSyntax
type Sql92UpdateFieldNameSyntax PgUpdateSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateFieldNameSyntax PgUpdateSyntax = PgFieldNameSyntax
type Sql92UpdateExpressionSyntax PgUpdateSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateExpressionSyntax PgUpdateSyntax = PgExpressionSyntax

Methods

updateStmt :: Sql92UpdateTableNameSyntax PgUpdateSyntax -> [(Sql92UpdateFieldNameSyntax PgUpdateSyntax, Sql92UpdateExpressionSyntax PgUpdateSyntax)] -> Maybe (Sql92UpdateExpressionSyntax PgUpdateSyntax) -> PgUpdateSyntax

type Sql92UpdateExpressionSyntax PgUpdateSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateExpressionSyntax PgUpdateSyntax = PgExpressionSyntax
type Sql92UpdateFieldNameSyntax PgUpdateSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateFieldNameSyntax PgUpdateSyntax = PgFieldNameSyntax
type Sql92UpdateTableNameSyntax PgUpdateSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92UpdateTableNameSyntax PgUpdateSyntax = PgTableNameSyntax

data PgDeleteSyntax Source #

IsSql92DeleteSyntax for Postgres

Instances

Instances details
IsSql92DeleteSyntax PgDeleteSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

Associated Types

type Sql92DeleteTableNameSyntax PgDeleteSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteTableNameSyntax PgDeleteSyntax = PgTableNameSyntax
type Sql92DeleteExpressionSyntax PgDeleteSyntax 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteExpressionSyntax PgDeleteSyntax = PgExpressionSyntax

Methods

deleteStmt :: Sql92DeleteTableNameSyntax PgDeleteSyntax -> Maybe Text -> Maybe (Sql92DeleteExpressionSyntax PgDeleteSyntax) -> PgDeleteSyntax

deleteSupportsAlias :: Proxy PgDeleteSyntax -> Bool

type Sql92DeleteExpressionSyntax PgDeleteSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteExpressionSyntax PgDeleteSyntax = PgExpressionSyntax
type Sql92DeleteTableNameSyntax PgDeleteSyntax Source # 
Instance details

Defined in Database.Beam.Postgres.Syntax

type Sql92DeleteTableNameSyntax PgDeleteSyntax = PgTableNameSyntax

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

json :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSON a) Source #

DataType for JSON. See PgJSON for more information

jsonb :: (ToJSON a, FromJSON a) => DataType Postgres (PgJSONB a) Source #

DataType for JSONB. See PgJSON for more information

uuid :: DataType Postgres UUID Source #

DataType for UUID columns. The pgCryptoGenRandomUUID function in the PgCrypto extension can be used to generate UUIDs at random.

money :: DataType Postgres PgMoney Source #

DataType for MONEY columns.

tsquery :: DataType Postgres TsQuery Source #

DataType for tsquery. See TsQuery for more information

tsvector :: DataType Postgres TsVector Source #

DataType for tsvector. See TsVector for more information

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.

Constructors

Inclusive 
Exclusive 

Instances

Instances details
Generic PgBoundType Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep PgBoundType 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep PgBoundType = D1 ('MetaData "PgBoundType" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" 'False) (C1 ('MetaCons "Inclusive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exclusive" 'PrefixI 'False) (U1 :: Type -> Type))
Show PgBoundType Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq PgBoundType Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Hashable PgBoundType Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep PgBoundType Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep PgBoundType = D1 ('MetaData "PgBoundType" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" 'False) (C1 ('MetaCons "Inclusive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exclusive" 'PrefixI 'False) (U1 :: Type -> Type))

data TsVectorConfig Source #

The identifier of a Postgres text search configuration.

Use the IsString instance to construct new values of this type

Instances

Instances details
IsString TsVectorConfig Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Show TsVectorConfig Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq TsVectorConfig Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Ord TsVectorConfig Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres TsVectorConfig Source # 
Instance details

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 # 
Instance details

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

newtype TsVector Source #

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

Instances details
Show TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Ord TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromField TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

ToField TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

toField :: TsVector -> Action #

FromBackendRow Postgres TsVector Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres TsVector Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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

newtype TsQuery Source #

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

Instances details
Show TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: TsQuery -> TsQuery -> Bool #

(/=) :: TsQuery -> TsQuery -> Bool #

Ord TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromField TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres TsQuery Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres TsQuery Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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.

newtype PgJSON a Source #

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

Instances details
IsPgJSON PgJSON Source # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

fromBackendRow :: FromBackendRowM Postgres (PgJSON a)

valuesNeeded :: Proxy Postgres -> Proxy (PgJSON a) -> Int

ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres (PgJSON a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

mempty :: PgJSON a #

mappend :: PgJSON a -> PgJSON a -> PgJSON a #

mconcat :: [PgJSON a] -> PgJSON a #

Semigroup a => Semigroup (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(<>) :: PgJSON a -> PgJSON a -> PgJSON a #

sconcat :: NonEmpty (PgJSON a) -> PgJSON a #

stimes :: Integral b => b -> PgJSON a -> PgJSON a #

Show a => Show (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

showsPrec :: Int -> PgJSON a -> ShowS #

show :: PgJSON a -> String #

showList :: [PgJSON a] -> ShowS #

Eq a => Eq (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgJSON a -> PgJSON a -> Bool #

(/=) :: PgJSON a -> PgJSON a -> Bool #

Ord a => Ord (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

compare :: PgJSON a -> PgJSON a -> Ordering #

(<) :: PgJSON a -> PgJSON a -> Bool #

(<=) :: PgJSON a -> PgJSON a -> Bool #

(>) :: PgJSON a -> PgJSON a -> Bool #

(>=) :: PgJSON a -> PgJSON a -> Bool #

max :: PgJSON a -> PgJSON a -> PgJSON a #

min :: PgJSON a -> PgJSON a -> PgJSON a #

Hashable a => Hashable (PgJSON a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

hashWithSalt :: Int -> PgJSON a -> Int #

hash :: PgJSON a -> Int #

(Typeable x, FromJSON x) => FromField (PgJSON x) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

newtype PgJSONB a Source #

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

Instances details
IsPgJSON PgJSONB Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres (PgJSONB a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

mempty :: PgJSONB a #

mappend :: PgJSONB a -> PgJSONB a -> PgJSONB a #

mconcat :: [PgJSONB a] -> PgJSONB a #

Semigroup a => Semigroup (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(<>) :: PgJSONB a -> PgJSONB a -> PgJSONB a #

sconcat :: NonEmpty (PgJSONB a) -> PgJSONB a #

stimes :: Integral b => b -> PgJSONB a -> PgJSONB a #

Show a => Show (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

showsPrec :: Int -> PgJSONB a -> ShowS #

show :: PgJSONB a -> String #

showList :: [PgJSONB a] -> ShowS #

Eq a => Eq (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgJSONB a -> PgJSONB a -> Bool #

(/=) :: PgJSONB a -> PgJSONB a -> Bool #

Ord a => Ord (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

compare :: PgJSONB a -> PgJSONB a -> Ordering #

(<) :: PgJSONB a -> PgJSONB a -> Bool #

(<=) :: PgJSONB a -> PgJSONB a -> Bool #

(>) :: PgJSONB a -> PgJSONB a -> Bool #

(>=) :: PgJSONB a -> PgJSONB a -> Bool #

max :: PgJSONB a -> PgJSONB a -> PgJSONB a #

min :: PgJSONB a -> PgJSONB a -> PgJSONB a #

Hashable a => Hashable (PgJSONB a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

hashWithSalt :: Int -> PgJSONB a -> Int #

hash :: PgJSONB a -> Int #

(Typeable x, FromJSON x) => FromField (PgJSONB x) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

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

Instances details
IsPgJSON PgJSON Source # 
Instance details

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 # 
Instance details

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

Instances details
Beamable (PgJSONEach valType) Source # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep (PgJSONEach valType f) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONEach valType f) = D1 ('MetaData "PgJSONEach" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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))))

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONEach valType f) = D1 ('MetaData "PgJSONEach" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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

Constructors

PgJSONKey 

Fields

Instances

Instances details
Beamable PgJSONKey Source # 
Instance details

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)) -> PgJSONKey f -> PgJSONKey g -> m (PgJSONKey h)

tblSkeleton :: TableSkeleton PgJSONKey

Generic (PgJSONKey f) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep (PgJSONKey f) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONKey f) = D1 ('MetaData "PgJSONKey" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" 'False) (C1 ('MetaCons "PgJSONKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "pgJsonKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Text))))

Methods

from :: PgJSONKey f -> Rep (PgJSONKey f) x #

to :: Rep (PgJSONKey f) x -> PgJSONKey f #

type Rep (PgJSONKey f) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONKey f) = D1 ('MetaData "PgJSONKey" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" 'False) (C1 ('MetaCons "PgJSONKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "pgJsonKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f Text))))

data PgJSONElement a (f :: Type -> Type) Source #

Constructors

PgJSONElement 

Fields

Instances

Instances details
Beamable (PgJSONElement a) Source # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep (PgJSONElement a f) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONElement a f) = D1 ('MetaData "PgJSONElement" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" 'False) (C1 ('MetaCons "PgJSONElement" 'PrefixI 'True) (S1 ('MetaSel ('Just "pgJsonElement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (C f a))))

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgJSONElement a f) = D1 ('MetaData "PgJSONElement" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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

newtype PgMoney Source #

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 

Instances

Instances details
Read PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Show PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgMoney -> PgMoney -> Bool #

(/=) :: PgMoney -> PgMoney -> Bool #

Ord PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromField PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

ToField PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

toField :: PgMoney -> Action #

FromBackendRow Postgres PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlValueSyntax PgValueSyntax PgMoney Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres PgMoney Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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_.

data PgPoint Source #

Constructors

PgPoint !Double !Double 

Instances

Instances details
Show PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgPoint -> PgPoint -> Bool #

(/=) :: PgPoint -> PgPoint -> Bool #

Ord PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromField PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlValueSyntax PgValueSyntax PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasDefaultSqlDataType Postgres PgPoint Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgPoint -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgPoint -> Proxy Postgres -> Bool -> [FieldCheck]

data PgLine Source #

Constructors

PgLine !Double !Double !Double 

Instances

Instances details
Show PgLine Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq PgLine Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgLine -> PgLine -> Bool #

(/=) :: PgLine -> PgLine -> Bool #

Ord PgLine Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlValueSyntax PgValueSyntax PgLine Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasDefaultSqlDataType Postgres PgLine Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgLine -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgLine -> Proxy Postgres -> Bool -> [FieldCheck]

data PgBox Source #

Constructors

PgBox !PgPoint !PgPoint 

Instances

Instances details
Show PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

showsPrec :: Int -> PgBox -> ShowS #

show :: PgBox -> String #

showList :: [PgBox] -> ShowS #

Eq PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgBox -> PgBox -> Bool #

(/=) :: PgBox -> PgBox -> Bool #

FromField PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

FromBackendRow Postgres PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlValueSyntax PgValueSyntax PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasDefaultSqlDataType Postgres PgBox Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

defaultSqlDataType :: Proxy PgBox -> Proxy Postgres -> Bool -> BeamSqlBackendDataTypeSyntax Postgres

defaultSqlDataTypeConstraints :: Proxy PgBox -> Proxy Postgres -> Bool -> [FieldCheck]

data PgPath Source #

Instances

Instances details
Show PgPath Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq PgPath Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgPath -> PgPath -> Bool #

(/=) :: PgPath -> PgPath -> Bool #

Ord PgPath Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

newtype PgRegex Source #

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.

Constructors

PgRegex Text 

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.

data PgSetOf (tbl :: (Type -> Type) -> Type) Source #

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.

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

Instances details
PgIsArrayContext QAggregateContext Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

mkArraySyntax :: Proxy QAggregateContext -> PgSyntax -> PgSyntax

PgIsArrayContext QValueContext Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

mkArraySyntax :: Proxy QValueContext -> PgSyntax -> PgSyntax

PgIsArrayContext QWindowingContext Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

mkArraySyntax :: Proxy QWindowingContext -> PgSyntax -> PgSyntax

PgIsArrayContext PgArrayValueContext Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

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 #

Index into the given array. This translates to the array[index] syntax in postgres. The beam operator name has been chosen to match the 'Data.Vector.(!)' operator.

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.

data PgRange n a Source #

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.

Instances

Instances details
(FromField a, Typeable a, Typeable n, Ord a) => FromBackendRow Postgres (PgRange n a) Source # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

HasSqlEqualityCheck Postgres (PgRange n a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep (PgRange n a) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgRange n a) = D1 ('MetaData "PgRange" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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))))

Methods

from :: PgRange n a -> Rep (PgRange n a) x #

to :: Rep (PgRange n a) x -> PgRange n a #

Show a => Show (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

showsPrec :: Int -> PgRange n a -> ShowS #

show :: PgRange n a -> String #

showList :: [PgRange n a] -> ShowS #

Eq a => Eq (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

(==) :: PgRange n a -> PgRange n a -> Bool #

(/=) :: PgRange n a -> PgRange n a -> Bool #

Hashable a => Hashable (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

hashWithSalt :: Int -> PgRange n a -> Int #

hash :: PgRange n a -> Int #

(FromField a, Typeable a, Typeable n, Ord a) => FromField (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

fromField :: FieldParser (PgRange n a) #

ToField (PGRange a) => ToField (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Methods

toField :: PgRange n a -> Action #

type Rep (PgRange n a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgRange n a) = D1 ('MetaData "PgRange" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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

Instances details
Generic (PgRangeBound a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Associated Types

type Rep (PgRangeBound a) 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgRangeBound a) = D1 ('MetaData "PgRangeBound" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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))))

Methods

from :: PgRangeBound a -> Rep (PgRangeBound a) x #

to :: Rep (PgRangeBound a) x -> PgRangeBound a #

Show a => Show (PgRangeBound a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Eq a => Eq (PgRangeBound a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

Hashable a => Hashable (PgRangeBound a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgRangeBound a) Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

type Rep (PgRangeBound a) = D1 ('MetaData "PgRangeBound" "Database.Beam.Postgres.PgSpecific" "beam-postgres-0.5.4.2-inplace" '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.

Methods

rangeName :: ByteString Source #

The range type name in the database.

data PgInt4Range Source #

Instances

Instances details
PgIsRange PgInt4Range Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

data PgInt8Range Source #

Instances

Instances details
PgIsRange PgInt8Range Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

data PgNumRange Source #

Instances

Instances details
PgIsRange PgNumRange Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

data PgTsRange Source #

Instances

Instances details
PgIsRange PgTsRange Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

data PgTsTzRange Source #

Instances

Instances details
PgIsRange PgTsTzRange Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

data PgDateRange Source #

Instances

Instances details
PgIsRange PgDateRange Source # 
Instance details

Defined in Database.Beam.Postgres.PgSpecific

range_ Source #

Arguments

:: forall n a context s. PgIsRange n 
=> PgBoundType

Lower bound type

-> PgBoundType

Upper bound type

-> QGenExpr context Postgres s (Maybe a)

. Lower bound value

-> QGenExpr context Postgres s (Maybe a)

. Upper bound value

-> 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 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 #

isEmpty_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #

lowerInc_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #

upperInc_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #

lowerInf_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool Source #

upperInf_ :: QGenExpr context Postgres s (PgRange n a) -> QGenExpr context Postgres s Bool 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.

now_ :: QExpr Postgres s LocalTime Source #

Postgres NOW() function. Returns the server's timestamp

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

Instances details
IsDatabaseEntity Postgres (PgExtensionEntity extension) Source # 
Instance details

Defined in Database.Beam.Postgres.Extensions

Associated Types

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) where
type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension

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 # 
Instance details

Defined in Database.Beam.Postgres.Extensions

Associated Types

newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) = CheckedPgExtension (DatabaseEntityDescriptor Postgres (PgExtensionEntity extension))
type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) 
Instance details

Defined in Database.Beam.Postgres.Extensions

type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension)

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

Instance details

Defined in Database.Beam.Postgres.Extensions

Methods

renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor Postgres (PgExtensionEntity e))

type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) Source # 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # 
Instance details

Defined in Database.Beam.Postgres.Extensions

data DatabaseEntityDescriptor Postgres (PgExtensionEntity extension) where
type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) Source # 
Instance details

Defined in Database.Beam.Postgres.Extensions

type DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension) = IsPgExtension extension
type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) Source # 
Instance details

Defined in Database.Beam.Postgres.Extensions

type CheckedDatabaseEntityDefaultRequirements Postgres (PgExtensionEntity extension) = DatabaseEntityRegularRequirements Postgres (PgExtensionEntity extension)
newtype CheckedDatabaseEntityDescriptor Postgres (PgExtensionEntity extension) Source # 
Instance details

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.

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

Instances details
PgDebugStmt (PgDeleteReturning a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

PgDebugStmt (PgInsertReturning a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

PgDebugStmt (PgUpdateReturning a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

PgDebugStmt (SqlDelete Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlDelete Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlInsert Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlInsert Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlSelect Postgres a) Source # 
Instance details

Defined in Database.Beam.Postgres.Debug

Methods

pgStmtSyntax :: SqlSelect Postgres a -> Maybe PgSyntax

PgDebugStmt (SqlUpdate Postgres a) Source # 
Instance details

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.

UnexpectedNull

A SQL NULL was encountered when the Haskell type did not permit it.

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).

data Connection #

Instances

Instances details
Eq Connection 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

data ConnectInfo #

Instances

Instances details
Generic ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Associated Types

type Rep ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

type Rep ConnectInfo = D1 ('MetaData "ConnectInfo" "Database.PostgreSQL.Simple.Internal" "postgresql-simple-0.7.0.0-b3b0425bd6acb29f239607217653a982d40489ef9c6ef5e14c3343b07aa23ef1" '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)))))
Read ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Show ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

Eq ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

type Rep ConnectInfo 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

type Rep ConnectInfo = D1 ('MetaData "ConnectInfo" "Database.PostgreSQL.Simple.Internal" "postgresql-simple-0.7.0.0-b3b0425bd6acb29f239607217653a982d40489ef9c6ef5e14c3343b07aa23ef1" '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 () #