Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class HasColumnNames entity tbl where
- colNames :: tbl (TableField tbl) -> (tbl (TableField tbl) -> entity) -> [ColumnName]
- tableSettings :: DatabaseEntity be db (TableEntity tbl) -> TableSettings tbl
- tableName :: Beamable tbl => DatabaseEntity be db (TableEntity tbl) -> TableName
- pkFieldNames :: (Beamable (PrimaryKey tbl), Table tbl) => DatabaseEntity be db (TableEntity tbl) -> [ColumnName]
- fieldAsColumnNames :: Beamable tbl => tbl (TableField c) -> [ColumnName]
- allColumnNames :: Beamable tbl => DatabaseEntity be db (TableEntity tbl) -> [ColumnName]
- hoistErrors :: Either e a -> Errors e a
- sequenceEither :: (Monoid e, Traversable f) => f (Either e a) -> Either e (f a)
- sequenceExceptT :: (Monad m, Monoid w, Traversable t) => t (ExceptT w m a) -> ExceptT w m (t a)
- sqlOptPrec :: Maybe Word -> Text
- sqlOptCharSet :: Maybe Text -> Text
- sqlEscaped :: Text -> Text
- sqlValidUnescaped :: Text -> Bool
- sqlIsReservedKeyword :: Text -> Bool
- postgresKeywordsReserved :: Set Text
- sqlSingleQuoted :: Text -> Text
- sqlOptNumericPrec :: Maybe (Word, Maybe Word) -> Text
Documentation
class HasColumnNames entity tbl where Source #
colNames :: tbl (TableField tbl) -> (tbl (TableField tbl) -> entity) -> [ColumnName] Source #
Instances
HasColumnNames (TableField tbl ty) tbl Source # | |
Defined in Database.Beam.AutoMigrate.Util colNames :: tbl (TableField tbl) -> (tbl (TableField tbl) -> TableField tbl ty) -> [ColumnName] Source # | |
Beamable (PrimaryKey tbl) => HasColumnNames (PrimaryKey tbl (TableField c)) tbl' Source # | |
Defined in Database.Beam.AutoMigrate.Util colNames :: tbl' (TableField tbl') -> (tbl' (TableField tbl') -> PrimaryKey tbl (TableField c)) -> [ColumnName] Source # | |
Beamable (PrimaryKey tbl) => HasColumnNames (PrimaryKey tbl (TableField c)) tbl Source # | |
Defined in Database.Beam.AutoMigrate.Util colNames :: tbl (TableField tbl) -> (tbl (TableField tbl) -> PrimaryKey tbl (TableField c)) -> [ColumnName] Source # |
tableSettings :: DatabaseEntity be db (TableEntity tbl) -> TableSettings tbl Source #
Extracts the TableSettings
out of the input DatabaseEntity
.
tableName :: Beamable tbl => DatabaseEntity be db (TableEntity tbl) -> TableName Source #
pkFieldNames :: (Beamable (PrimaryKey tbl), Table tbl) => DatabaseEntity be db (TableEntity tbl) -> [ColumnName] Source #
Extracts the primary key of a table as a list of ColumnName
.
fieldAsColumnNames :: Beamable tbl => tbl (TableField c) -> [ColumnName] Source #
Similar to pkFieldNames
, but it works on any entity that derives Beamable
.
allColumnNames :: Beamable tbl => DatabaseEntity be db (TableEntity tbl) -> [ColumnName] Source #
Returns all the ColumnName
s for a given DatabaseEntity
.
hoistErrors :: Either e a -> Errors e a Source #
sequenceEither :: (Monoid e, Traversable f) => f (Either e a) -> Either e (f a) Source #
sequenceExceptT :: (Monad m, Monoid w, Traversable t) => t (ExceptT w m a) -> ExceptT w m (t a) Source #
Evaluate each action in sequence, accumulating all errors in case of a failure. Note that this means each action will be run independently, regardless of failure.
sqlEscaped :: Text -> Text Source #
Escape a sql identifier according to the rules defined in the postgres manual
sqlValidUnescaped :: Text -> Bool Source #
Check whether an identifier is valid without escaping (True) or must be escaped (False) according to the postgres manual
sqlIsReservedKeyword :: Text -> Bool Source #
postgresKeywordsReserved :: Set Text Source #
Reserved keywords according to https://www.postgresql.org/docs/current/sql-keywords-appendix.html
sqlSingleQuoted :: Text -> Text Source #