Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Beam.Postgres.CustomTypes
Documentation
Instances
IsDatabaseEntity Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes Associated Types
Methods dbEntityName :: Lens' (DatabaseEntityDescriptor Postgres (PgType a)) Text dbEntitySchema :: Traversal' (DatabaseEntityDescriptor Postgres (PgType a)) (Maybe Text) dbEntityAuto :: Text -> DatabaseEntityDescriptor Postgres (PgType a) | |||||||||||||
IsCheckedDatabaseEntity Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes Associated Types
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) | |||||||||||||
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor Postgres (PgType a))) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes | |||||||||||||
type DatabaseEntityDefaultRequirements Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes type DatabaseEntityDefaultRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a, IsPgCustomDataType a) | |||||||||||||
data DatabaseEntityDescriptor Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes data DatabaseEntityDescriptor Postgres (PgType a) where
| |||||||||||||
type DatabaseEntityRegularRequirements Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes type DatabaseEntityRegularRequirements Postgres (PgType a) = (HasSqlValueSyntax PgValueSyntax a, FromBackendRow Postgres a) | |||||||||||||
type CheckedDatabaseEntityDefaultRequirements Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes | |||||||||||||
data CheckedDatabaseEntityDescriptor Postgres (PgType a) Source # | |||||||||||||
Defined in Database.Beam.Postgres.CustomTypes data CheckedDatabaseEntityDescriptor Postgres (PgType a) where
|
newtype PgTypeCheck Source #
Constructors
PgTypeCheck (Text -> SomeDatabasePredicate) |
data PgDataTypeSchema a Source #
class IsPgCustomDataType a where Source #
Methods
pgDataTypeName :: Proxy a -> Text Source #
Instances
class HasSqlValueSyntax expr ty #
Minimal complete definition
sqlValueSyntax
Instances
HasSqlValueSyntax Value SqlNull | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: SqlNull -> Value | |
HasSqlValueSyntax Value ByteString | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: ByteString -> Value | |
HasSqlValueSyntax Value Int16 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Int16 -> Value | |
HasSqlValueSyntax Value Int32 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Int32 -> Value | |
HasSqlValueSyntax Value Int64 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Int64 -> Value | |
HasSqlValueSyntax Value Word16 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Word16 -> Value | |
HasSqlValueSyntax Value Word32 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Word32 -> Value | |
HasSqlValueSyntax Value Word64 | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Word64 -> Value | |
HasSqlValueSyntax Value Text | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Text -> Value | |
HasSqlValueSyntax Value Day | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Day -> Value | |
HasSqlValueSyntax Value UTCTime | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: UTCTime -> Value | |
HasSqlValueSyntax Value LocalTime | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: LocalTime -> Value | |
HasSqlValueSyntax Value TimeOfDay | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: TimeOfDay -> Value | |
HasSqlValueSyntax Value Integer | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Integer -> Value | |
HasSqlValueSyntax Value String | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: String -> Value | |
HasSqlValueSyntax Value Bool | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Bool -> Value | |
HasSqlValueSyntax Value Double | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Double -> Value | |
(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasSqlValueSyntax Value Int | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Int -> Value | |
(TypeError (PreferExplicitSize Word Word32) :: Constraint) => HasSqlValueSyntax Value Word | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Word -> Value | |
HasSqlValueSyntax SqlSyntaxBuilder SqlNull | |
Defined in Database.Beam.Backend.SQL.Builder Methods sqlValueSyntax :: SqlNull -> SqlSyntaxBuilder | |
HasSqlValueSyntax SqlSyntaxBuilder Int32 | |
Defined in Database.Beam.Backend.SQL.Builder Methods sqlValueSyntax :: Int32 -> SqlSyntaxBuilder | |
HasSqlValueSyntax SqlSyntaxBuilder Text | |
Defined in Database.Beam.Backend.SQL.Builder Methods sqlValueSyntax :: Text -> SqlSyntaxBuilder | |
HasSqlValueSyntax SqlSyntaxBuilder Bool | |
Defined in Database.Beam.Backend.SQL.Builder Methods sqlValueSyntax :: Bool -> SqlSyntaxBuilder | |
(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasSqlValueSyntax SqlSyntaxBuilder Int | |
Defined in Database.Beam.Backend.SQL.Builder Methods sqlValueSyntax :: Int -> SqlSyntaxBuilder | |
HasSqlValueSyntax HsExpr Int32 | |
Defined in Database.Beam.Haskell.Syntax Methods sqlValueSyntax :: Int32 -> HsExpr | |
HasSqlValueSyntax HsExpr Bool | |
Defined in Database.Beam.Haskell.Syntax Methods sqlValueSyntax :: Bool -> HsExpr | |
HasSqlValueSyntax PgValueSyntax Value Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Value -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax SqlNull Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: SqlNull -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgBox -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax PgLine Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgLineSegment Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax PgRegex Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods | |
HasSqlValueSyntax PgValueSyntax ByteString Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax ByteString Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Int16 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Int16 -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Int32 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Int32 -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Int64 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Int64 -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Int8 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Int8 -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Word16 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Word32 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Word64 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Word8 Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Word8 -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Oid Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Oid -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax HStoreBuilder Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax HStoreList Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax HStoreMap Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Date Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Date -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax LocalTimestamp Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax UTCTimestamp Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Scientific Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Text Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Text -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Text Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Text -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Day Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Day -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax NominalDiffTime Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax UTCTime Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax LocalTime Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax TimeOfDay Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax UUID Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: UUID -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Integer Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Bool Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Bool -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax Double Source # | |
Defined in Database.Beam.Postgres.Syntax Methods | |
HasSqlValueSyntax PgValueSyntax Float Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Float -> PgValueSyntax | |
(TypeError (PreferExplicitSize Int Int32) :: Constraint) => HasSqlValueSyntax PgValueSyntax Int Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Int -> PgValueSyntax | |
(TypeError (PreferExplicitSize Word Word32) :: Constraint) => HasSqlValueSyntax PgValueSyntax Word Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Word -> PgValueSyntax | |
HasSqlValueSyntax Value x => HasSqlValueSyntax Value (Maybe x) | |
Defined in Database.Beam.Backend.SQL.AST Methods sqlValueSyntax :: Maybe x -> Value | |
ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgJSON a -> PgValueSyntax | |
ToJSON a => HasSqlValueSyntax PgValueSyntax (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgJSONB a -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax (CI Text) Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: CI Text -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax (CI Text) Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: CI Text -> PgValueSyntax | |
ToField a => HasSqlValueSyntax PgValueSyntax (Vector a) Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Vector a -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax x => HasSqlValueSyntax PgValueSyntax (Maybe x) Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: Maybe x -> PgValueSyntax | |
HasSqlValueSyntax PgValueSyntax [Char] Source # | |
Defined in Database.Beam.Postgres.Syntax Methods sqlValueSyntax :: [Char] -> PgValueSyntax | |
HasSqlValueSyntax syntax x => HasSqlValueSyntax syntax (SqlSerial x) | |
Defined in Database.Beam.Backend.SQL.SQL92 Methods sqlValueSyntax :: SqlSerial x -> syntax | |
(HasSqlValueSyntax PgValueSyntax a, PgIsRange n) => HasSqlValueSyntax PgValueSyntax (PgRange n a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods sqlValueSyntax :: PgRange n a -> PgValueSyntax | |
HasSqlValueSyntax vs t => HasSqlValueSyntax vs (Tagged tag t) | |
Defined in Database.Beam.Backend.SQL.SQL92 Methods sqlValueSyntax :: Tagged tag t -> vs |
class BeamBackend be => FromBackendRow be a #
Instances
FromBackendRow Postgres Value Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Value | |
FromBackendRow Postgres SqlNull Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres SqlNull valuesNeeded :: Proxy Postgres -> Proxy SqlNull -> Int | |
FromBackendRow Postgres PgBox Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres PgBox | |
FromBackendRow Postgres PgMoney Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres PgMoney | |
FromBackendRow Postgres PgPoint Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres PgPoint | |
FromBackendRow Postgres TsQuery Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres TsQuery | |
FromBackendRow Postgres TsVector Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres TsVector | |
FromBackendRow Postgres ByteString Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres ByteString valuesNeeded :: Proxy Postgres -> Proxy ByteString -> Int | |
FromBackendRow Postgres ByteString Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres ByteString valuesNeeded :: Proxy Postgres -> Proxy ByteString -> Int | |
FromBackendRow Postgres Int16 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Int16 | |
FromBackendRow Postgres Int32 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Int32 | |
FromBackendRow Postgres Int64 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Int64 | |
FromBackendRow Postgres Word16 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Word16 | |
FromBackendRow Postgres Word32 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Word32 | |
FromBackendRow Postgres Word64 Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Word64 | |
FromBackendRow Postgres Oid Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Oid | |
FromBackendRow Postgres HStoreList Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres HStoreList valuesNeeded :: Proxy Postgres -> Proxy HStoreList -> Int | |
FromBackendRow Postgres HStoreMap Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres HStoreMap | |
FromBackendRow Postgres Date Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Date | |
FromBackendRow Postgres LocalTimestamp Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres LocalTimestamp valuesNeeded :: Proxy Postgres -> Proxy LocalTimestamp -> Int | |
FromBackendRow Postgres UTCTimestamp Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres UTCTimestamp valuesNeeded :: Proxy Postgres -> Proxy UTCTimestamp -> Int | |
FromBackendRow Postgres ZonedTimestamp Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres ZonedTimestamp valuesNeeded :: Proxy Postgres -> Proxy ZonedTimestamp -> Int | |
FromBackendRow Postgres Null Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Null | |
FromBackendRow Postgres Scientific Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Scientific valuesNeeded :: Proxy Postgres -> Proxy Scientific -> Int | |
FromBackendRow Postgres Text Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Text | |
FromBackendRow Postgres Text Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Text | |
FromBackendRow Postgres Day Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Day | |
FromBackendRow Postgres UTCTime Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres UTCTime | |
FromBackendRow Postgres LocalTime Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres LocalTime | |
FromBackendRow Postgres TimeOfDay Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres TimeOfDay | |
FromBackendRow Postgres UUID Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres UUID | |
FromBackendRow Postgres Integer Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Integer | |
FromBackendRow Postgres Bool Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Bool | |
FromBackendRow Postgres Char Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Char | |
FromBackendRow Postgres Double Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Double | |
(TypeError (PreferExplicitSize Int Int32) :: Constraint) => FromBackendRow Postgres Int Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Int | |
(TypeError (PreferExplicitSize Word Word32) :: Constraint) => FromBackendRow Postgres Word Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Word | |
BeamBackend be => FromBackendRow be () | |
Defined in Database.Beam.Backend.SQL.Row | |
(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSON a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgJSON a) | |
(Typeable a, FromJSON a) => FromBackendRow Postgres (PgJSONB a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgJSONB a) | |
FromBackendRow Postgres (CI Text) Source # | |
Defined in Database.Beam.Postgres.Types | |
FromBackendRow Postgres (CI Text) Source # | |
Defined in Database.Beam.Postgres.Types | |
FromBackendRow Postgres (Ratio Integer) Source # | |
Defined in Database.Beam.Postgres.Types | |
(FromField a, Typeable a) => FromBackendRow Postgres (PGRange a) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (PGRange a) | |
FromBackendRow Postgres (Binary ByteString) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (Binary ByteString) valuesNeeded :: Proxy Postgres -> Proxy (Binary ByteString) -> Int | |
FromBackendRow Postgres (Binary ByteString) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (Binary ByteString) valuesNeeded :: Proxy Postgres -> Proxy (Binary ByteString) -> Int | |
(FromField a, Typeable a) => FromBackendRow Postgres (PGArray a) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (PGArray a) | |
(FromField a, Typeable a) => FromBackendRow Postgres (Vector a) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (Vector a) | |
FromBackendRow Postgres [Char] Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres [Char] | |
FromBackendRow be x => FromBackendRow be (SqlSerial x) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (SqlSerial x) valuesNeeded :: Proxy be -> Proxy (SqlSerial x) -> Int | |
FromBackendRow be a => FromBackendRow be (Identity a) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (Identity a) valuesNeeded :: Proxy be -> Proxy (Identity a) -> Int | |
(FromBackendRow be x, FromBackendRow be SqlNull) => FromBackendRow be (Maybe x) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (Maybe x) valuesNeeded :: Proxy be -> Proxy (Maybe x) -> Int | |
(BeamBackend be, Generic (tbl (Nullable Identity)), Generic (tbl (Nullable Exposed)), GFromBackendRow be (Rep (tbl (Nullable Exposed))) (Rep (tbl (Nullable Identity)))) => FromBackendRow be (tbl (Nullable Identity)) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (tbl (Nullable Identity)) valuesNeeded :: Proxy be -> Proxy (tbl (Nullable Identity)) -> Int | |
(BeamBackend be, Generic (tbl Identity), Generic (tbl Exposed), GFromBackendRow be (Rep (tbl Exposed)) (Rep (tbl Identity))) => FromBackendRow be (tbl Identity) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (tbl Identity) valuesNeeded :: Proxy be -> Proxy (tbl Identity) -> Int | |
(FromField a, Typeable a, Typeable n, Ord a) => FromBackendRow Postgres (PgRange n a) Source # | |
Defined in Database.Beam.Postgres.PgSpecific Methods fromBackendRow :: FromBackendRowM Postgres (PgRange n a) valuesNeeded :: Proxy Postgres -> Proxy (PgRange n a) -> Int | |
(FromField a, FromField b, Typeable a, Typeable b) => FromBackendRow Postgres (Either a b) Source # | |
Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres (Either a b) | |
(BeamBackend be, KnownNat n, FromBackendRow be a) => FromBackendRow be (Vector n a) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (Vector n a) valuesNeeded :: Proxy be -> Proxy (Vector n a) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b) => FromBackendRow be (a, b) | |
Defined in Database.Beam.Backend.SQL.Row | |
(BeamBackend be, FromBackendRow be t) => FromBackendRow be (Tagged tag t) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (Tagged tag t) valuesNeeded :: Proxy be -> Proxy (Tagged tag t) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c) => FromBackendRow be (a, b, c) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c) valuesNeeded :: Proxy be -> Proxy (a, b, c) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d) => FromBackendRow be (a, b, c, d) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c, d) valuesNeeded :: Proxy be -> Proxy (a, b, c, d) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e) => FromBackendRow be (a, b, c, d, e) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c, d, e) valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f) => FromBackendRow be (a, b, c, d, e, f) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f) valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f, FromBackendRow be g) => FromBackendRow be (a, b, c, d, e, f, g) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f, g) valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f, g) -> Int | |
(BeamBackend be, FromBackendRow be a, FromBackendRow be b, FromBackendRow be c, FromBackendRow be d, FromBackendRow be e, FromBackendRow be f, FromBackendRow be g, FromBackendRow be h) => FromBackendRow be (a, b, c, d, e, f, g, h) | |
Defined in Database.Beam.Backend.SQL.Row Methods fromBackendRow :: FromBackendRowM be (a, b, c, d, e, f, g, h) valuesNeeded :: Proxy be -> Proxy (a, b, c, d, e, f, g, h) -> Int |
pgCustomEnumSchema :: HasSqlValueSyntax PgValueSyntax a => [a] -> PgDataTypeSchema a Source #
pgBoundedEnumSchema :: (Enum a, Bounded a, HasSqlValueSyntax PgValueSyntax a) => PgDataTypeSchema a Source #
pgCustomEnumActionProvider :: ActionProvider Postgres Source #
pgCreateEnumActionProvider :: ActionProvider Postgres Source #
pgDropEnumActionProvider :: ActionProvider Postgres Source #
pgChecksForTypeSchema :: PgDataTypeSchema a -> [PgTypeCheck] Source #
pgEnumValueSyntax :: (a -> String) -> a -> PgValueSyntax Source #
createEnum :: forall a (db :: (Type -> Type) -> Type). (HasSqlValueSyntax PgValueSyntax a, Enum a, Bounded a) => Text -> Migration Postgres (CheckedDatabaseEntity Postgres db (PgType a)) Source #