beam-migrate-0.5.2.0: SQL DDL support and migrations support library for Beam
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Beam.Migrate.Generics

Description

Support for creating checked databases from Haskell ADTs, using Generics.

For more information, see the manual

Synopsis

Default checked database settings

defaultMigratableDbSettings :: forall be db. (Generic (CheckedDatabaseSettings be db), GAutoMigratableDb be (Rep (CheckedDatabaseSettings be db))) => CheckedDatabaseSettings be db Source #

Produce a checked database for the given Haskell database type

See the manual for more information on the defaults.

Extending the defaulting sytem

class BeamMigrateSqlBackend be => HasDefaultSqlDataType be ty where Source #

Used to define a default SQL data type for a haskell type in a particular backend, as well as any constraints that are needed

Beam defines instances for several standard SQL types, which are polymorphic over any standard data type syntax. Backends or extensions which provide custom types should instantiate instances of this class for any types they provide for which they would like checked schema migrations

Minimal complete definition

defaultSqlDataType

Methods

defaultSqlDataType Source #

Arguments

:: Proxy ty

Concrete representation of the type

-> Proxy be

Concrete representation of the backend

-> Bool

True if this field is in an embedded key or table, False otherwise

-> BeamSqlBackendDataTypeSyntax be 

Provide a data type for the given type

defaultSqlDataTypeConstraints Source #

Arguments

:: Proxy ty

Concrete representation of the type

-> Proxy be

Concrete representation of the backend

-> Bool

True if this field is embedded in a foreign key, False otherwise. For example, SERIAL types in postgres get a DEFAULT constraint, but SERIAL types in a foreign key do not.

-> [FieldCheck] 

Provide arbitrary constraints on a field of the requested type. See FieldCheck for more information on the formatting of constraints.

Instances

Instances details
BeamMigrateSqlBackend be => HasDefaultSqlDataType be Int16 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Int16 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Int16 -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Int32 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Int32 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Int32 -> Proxy be -> Bool -> [FieldCheck] Source #

(BeamMigrateSqlBackend be, BeamSqlT071Backend be) => HasDefaultSqlDataType be Int64 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Int64 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Int64 -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Word16 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Word16 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Word16 -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Word32 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Word32 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Word32 -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Word64 Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Word64 -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Word64 -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be SqlBitString Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy SqlBitString -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy SqlBitString -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Scientific Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Scientific -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Scientific -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Text Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Text -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Text -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Day Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Day -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Day -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be TimeOfDay Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy TimeOfDay -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy TimeOfDay -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSql99Backend be => HasDefaultSqlDataType be Bool Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Bool -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Bool -> Proxy be -> Bool -> [FieldCheck] Source #

BeamMigrateSqlBackend be => HasDefaultSqlDataType be Double Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Double -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Double -> Proxy be -> Bool -> [FieldCheck] Source #

(TypeError (PreferExplicitSize Int Int32) :: Constraint, BeamMigrateSqlBackend be) => HasDefaultSqlDataType be Int Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Int -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Int -> Proxy be -> Bool -> [FieldCheck] Source #

(TypeError (PreferExplicitSize Word Word32) :: Constraint, BeamMigrateSqlBackend be) => HasDefaultSqlDataType be Word Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy Word -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy Word -> Proxy be -> Bool -> [FieldCheck] Source #

(BeamMigrateSqlBackend be, HasDefaultSqlDataType be ty) => HasDefaultSqlDataType be (Maybe ty) Source # 
Instance details

Defined in Database.Beam.Migrate.Generics.Tables

Methods

defaultSqlDataType :: Proxy (Maybe ty) -> Proxy be -> Bool -> BeamSqlBackendDataTypeSyntax be Source #

defaultSqlDataTypeConstraints :: Proxy (Maybe ty) -> Proxy be -> Bool -> [FieldCheck] Source #

class BeamMigrateSqlBackend be => HasNullableConstraint (x :: Bool) be Source #

Minimal complete definition

nullableConstraint

type family NullableStatus (x :: *) :: Bool where ... Source #

Equations

NullableStatus (Maybe x) = 'True 
NullableStatus x = 'False