beam-core-0.6.0.0: Type-safe, feature-complete SQL query and manipulation interface for Haskell

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Schema.Tables

Contents

Description

Defines a generic schema type that can be used to define schemas for Beam tables

Synopsis

Database Types

class Database db where Source #

Allows introspection into database types.

All database types must be of kind '(* -> *) -> *'. If the type parameter is named f, each field must be of the type of f applied to some type for which an IsDatabaseEntity instance exists.

Entities are documented under the corresponding section and in the manual

Methods

zipTables :: Monad m => Proxy be -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h) Source #

Default derived function. Do not implement this yourself.

The idea is that, for any two databases over particular entity tags f and g, if we can take any entity in f and g to the corresponding entity in h (in the possibly effectful monad m), then we can transform the two databases over f and g to a database in h, within the monad m.

If that doesn't make sense, don't worry. This is mostly beam internal

zipTables :: (Generic (db f), Generic (db g), Generic (db h), Monad m, GZipDatabase be f g h (Rep (db f)) (Rep (db g)) (Rep (db h))) => Proxy be -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h) Source #

Default derived function. Do not implement this yourself.

The idea is that, for any two databases over particular entity tags f and g, if we can take any entity in f and g to the corresponding entity in h (in the possibly effectful monad m), then we can transform the two databases over f and g to a database in h, within the monad m.

If that doesn't make sense, don't worry. This is mostly beam internal

zipTables :: (Database db, Monad m) => Proxy be -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h) Source #

Default derived function. Do not implement this yourself.

The idea is that, for any two databases over particular entity tags f and g, if we can take any entity in f and g to the corresponding entity in h (in the possibly effectful monad m), then we can transform the two databases over f and g to a database in h, within the monad m.

If that doesn't make sense, don't worry. This is mostly beam internal

type DatabaseSettings be db = db (DatabaseEntity be db) Source #

When parameterized by this entity tag, a database type will hold meta-information on the Haskell mappings of database entities. Under the hood, each entity type is transformed into its DatabaseEntityDescriptor type. For tables this includes the table name as well as the corresponding TableSettings, which provides names for each column.

class RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be entityType)) => IsDatabaseEntity be entityType where Source #

Minimal complete definition

dbEntityName, dbEntityAuto

Associated Types

data DatabaseEntityDescriptor be entityType :: * Source #

type DatabaseEntityDefaultRequirements be entityType :: Constraint Source #

type DatabaseEntityRegularRequirements be entityType :: Constraint Source #

data DatabaseEntity be (db :: (* -> *) -> *) entityType where Source #

Represents a meta-description of a particular entityType. Mostly, a wrapper around 'DatabaseEntityDescriptor be entityType', but carries around the IsDatabaseEntity dictionary.

Constructors

DatabaseEntity :: IsDatabaseEntity be entityType => DatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType 

type DatabaseModification f be db = db (EntityModification f be) Source #

A helper data type that lets you modify a database schema. Converts all entities in the database into functions from that entity to itself.

newtype EntityModification f be e Source #

A newtype wrapper around 'f e -> f e' (i.e., an endomorphism between entity types in f). You usually want to use modifyTable or another function to contstruct these for you.

Constructors

EntityModification (f e -> f e) 

newtype FieldModification f a Source #

A newtype wrapper around 'Columnar f a -> Columnar f ' (i.e., an endomorphism between Columnars over f). You usually want to use fieldNamed or the IsString instance to rename the field, when 'f ~ TableField'

Constructors

FieldModification (Columnar f a -> Columnar f a) 

dbModification :: forall f be db. Database db => DatabaseModification f be db Source #

Return a DatabaseModification that does nothing. This is useful if you only want to rename one table. You can do

dbModification { tbl1 = modifyTable (\oldNm -> "NewTableName") tableModification }

tableModification :: forall f tbl. Beamable tbl => tbl (FieldModification f) Source #

Return a table modification (for use with modifyTable) that does nothing. Useful if you only want to change the table name, or if you only want to modify a few fields.

For example,

tableModification { field1 = "Column1" }

is a table modification (where 'f ~ TableField tbl') that changes the column name of field1 to Column1.

withDbModification :: forall db be entity. Database db => db (entity be db) -> DatabaseModification (entity be db) be db -> db (entity be db) Source #

Modify a database according to a given modification. Most useful for DatabaseSettings to change the name mappings of tables and fields. For example, you can use this to modify the default names of a table

db :: DatabaseSettings MyDb
db = defaultDbSettings `withDbModification`
     dbModification {
       -- Change default name "table1" to "Table_1". Change the name of "table1Field1" to "first_name"
       table1 = modifyTable (\_ -> "Table_1") (tableModification { table1Field1 = "first_name" }
     }

withTableModification :: Beamable tbl => tbl (FieldModification f) -> tbl f -> tbl f Source #

Modify a table according to the given field modifications. Invoked by modifyTable to apply the modification in the database. Not used as often in user code, but provided for completeness.

modifyTable :: (Text -> Text) -> tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl) Source #

Provide an EntityModification for TableEntitys. Allows you to modify the name of the table and provide a modification for each field in the table. See the examples for withDbModification for more.

fieldNamed :: Text -> FieldModification (TableField tbl) a Source #

A field modification to rename the field. Also offered under the IsString instance for 'FieldModification (TableField tbl) a' for convenience.

defaultDbSettings :: (Generic (DatabaseSettings be db), GAutoDbSettings (Rep (DatabaseSettings be db) ())) => DatabaseSettings be db Source #

Automatically provide names for tables, and descriptions for tables (using defTblFieldSettings). Your database must implement Generic, and must be auto-derivable. For more information on name generation, see the manual

class RenamableField f where Source #

Minimal complete definition

renameField

Methods

renameField :: Proxy f -> Proxy a -> (Text -> Text) -> Columnar f a -> Columnar f a Source #

Instances

RenamableField (TableField tbl) Source # 

Methods

renameField :: Proxy (* -> *) (TableField tbl) -> Proxy * a -> (Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source #

data Lenses (t :: (* -> *) -> *) (f :: * -> *) x Source #

data LensFor t x where Source #

Constructors

LensFor :: Generic t => Lens' t x -> LensFor t x 

Columnar and Column Tags

type family Columnar (f :: * -> *) x where ... Source #

A type family that we use to "tag" columns in our table datatypes.

This is what allows us to use the same table type to hold table data, describe table settings, derive lenses, and provide expressions.

The basic rules are

Columnar Identity x = x

Thus, any Beam table applied to Identity will yield a simplified version of the data type, that contains just what you'd expect.

The Nullable type is used when referencing PrimaryKeys that we want to include optionally. For example, if we have a table with a PrimaryKey, like the following

data BeamTableT f = BeamTableT
                  { _refToAnotherTable :: PrimaryKey AnotherTableT f
                  , ... }

we would typically be required to provide values for the PrimaryKey embedded into BeamTableT. We can use Nullable to lift this constraint.

data BeamTableT f = BeamTableT
                  { _refToAnotherTable :: PrimaryKey AnotherTableT (Nullable f)
                  , ... }

Now we can use justRef and nothingRef to refer to this table optionally. The embedded PrimaryKey in _refToAnotherTable automatically has its fields converted into Maybe using Nullable.

The last Columnar rule is

Columnar f x = f x

Use this rule if you'd like to parameterize your table type over any other functor. For example, this is used in the query modules to write expressions such as 'TableT QExpr', which returns a table whose fields have been turned into query expressions.

The other rules are used within Beam to provide lenses and to expose the inner structure of the data type.

Equations

Columnar Exposed x = Exposed x 
Columnar Identity x = x 
Columnar (Lenses t f) x = LensFor (t f) (Columnar f x) 
Columnar (Nullable c) x = Columnar c (Maybe x) 
Columnar f x = f x 

type C f a = Columnar f a Source #

A short type-alias for Columnar. May shorten your schema definitions

newtype Columnar' f a Source #

If you declare a function 'Columnar f a -> b' and try to constrain your function by a type class for f, GHC will complain, because f is ambiguous in 'Columnar f a'. For example, 'Columnar Identity (Maybe a) ~ Maybe a' and 'Columnar (Nullable Identity) a ~ Maybe a', so given a type 'Columnar f a', we cannot know the type of f.

Thus, if you need to know f, you can instead use Columnar'. Since its a newtype, it carries around the f paramater unambiguously. Internally, it simply wraps 'Columnar f a'

Constructors

Columnar' (Columnar f a) 

data Nullable (c :: * -> *) x Source #

Support for NULLable Foreign Key references.

data MyTable f = MyTable
               { nullableRef :: PrimaryKey AnotherTable (Nullable f)
               , ... }
                deriving (Generic, Typeable)

See Columnar for more information.

Instances

(Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate syntax (t (Nullable (QGenExpr context syntax s))) Source # 

Methods

project' :: Monad m => Proxy (* -> Constraint) contextPredicate -> (forall context0. contextPredicate context0 => Proxy * context0 -> WithExprContext syntax -> m (WithExprContext syntax)) -> t (Nullable (QGenExpr context syntax s)) -> m (t (Nullable (QGenExpr context syntax s))) Source #

(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)) Source # 
Beamable tbl => ThreadRewritable s (tbl (Nullable (QGenExpr ctxt syntax s))) Source # 

Associated Types

type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) :: * Source #

Methods

rewriteThread :: Proxy * s' -> tbl (Nullable (QGenExpr ctxt syntax s)) -> WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source #

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable t) => SqlDeconstructMaybe syntax (t (Nullable (QExpr syntax s))) (t (QExpr syntax s)) s Source # 

Methods

isJust_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

isNothing_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

maybe_ :: QExpr syntax s y -> (t (QExpr syntax s) -> QExpr syntax s y) -> t (Nullable (QExpr syntax s)) -> QExpr syntax s y Source #

FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 * R (t (Nullable Exposed))) (K1 * R (t (Nullable Identity))) (K1 * R (t (Nullable (WithConstraint c)))) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (K1 * R (t (Nullable Exposed))) -> K1 * R (t (Nullable Identity)) () -> K1 * R (t (Nullable (WithConstraint c))) () Source #

Beamable tbl => ContextRewritable (tbl (Nullable (QGenExpr old syntax s))) Source # 

Associated Types

type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt :: * Source #

Methods

rewriteContext :: Proxy * ctxt -> tbl (Nullable (QGenExpr old syntax s)) -> WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source #

(Beamable table, IsSql92ExpressionSyntax syntax, FieldsFulfillConstraintNullable (HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax)) table) => SqlValable (table (Nullable (QGenExpr ctxt syntax s))) Source # 

Methods

val_ :: HaskellLiteralForQExpr (table (Nullable (QGenExpr ctxt syntax s))) -> table (Nullable (QGenExpr ctxt syntax s)) Source #

TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # 

Methods

reduceTag :: Functor m => (Columnar' f' a' -> m (Columnar' f' a')) -> Columnar' (Nullable f) a -> m (Columnar' (Nullable f) a) Source #

Table t => SqlJustable (t Identity) (t (Nullable Identity)) Source # 
(Table t, IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) SqlNull) => SqlJustable (t (QExpr syntax s)) (t (Nullable (QExpr syntax s))) Source # 

Methods

just_ :: t (QExpr syntax s) -> t (Nullable (QExpr syntax s)) Source #

nothing_ :: t (Nullable (QExpr syntax s)) Source #

Table t => SqlJustable (PrimaryKey t Identity) (PrimaryKey t (Nullable Identity)) Source # 
(Table t, IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) SqlNull) => SqlJustable (PrimaryKey t (QExpr syntax s)) (PrimaryKey t (Nullable (QExpr syntax s))) Source # 

Methods

just_ :: PrimaryKey t (QExpr syntax s) -> PrimaryKey t (Nullable (QExpr syntax s)) Source #

nothing_ :: PrimaryKey t (Nullable (QExpr syntax s)) Source #

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable tbl) => SqlEq (QGenExpr context syntax s) (tbl (Nullable (QGenExpr context syntax s))) Source # 

Methods

(==.) :: tbl (Nullable (QGenExpr context syntax s)) -> tbl (Nullable (QGenExpr context syntax s)) -> QGenExpr context syntax s Bool Source #

(/=.) :: tbl (Nullable (QGenExpr context syntax s)) -> tbl (Nullable (QGenExpr context syntax s)) -> QGenExpr context syntax s Bool Source #

type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source # 
type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) = tbl (Nullable (QGenExpr ctxt syntax s'))
type QExprToIdentity (table (Nullable c)) Source # 
type QExprToIdentity (table (Nullable c)) = Maybe (QExprToIdentity (table c))
type HaskellLiteralForQExpr (table (Nullable f)) Source # 
type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # 
type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt = tbl (Nullable (QGenExpr ctxt syntax s))

data TableField (table :: (* -> *) -> *) ty Source #

Metadata for a field of type ty in table.

Essentially a wrapper over the field name, but with a phantom type parameter, so that it forms an appropriate column tag.

Usually you use the defaultDbSettings function to generate an appropriate naming convention for you, and then modify it with withDbModification if necessary. Under this scheme, the field can be renamed using the IsString instance for TableField, or the fieldNamed function.

Constructors

TableField 

Fields

Instances

RenamableField (TableField tbl) Source # 

Methods

renameField :: Proxy (* -> *) (TableField tbl) -> Proxy * a -> (Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source #

TagReducesTo (TableField tbl) (TableField tbl) Source # 

Methods

reduceTag :: Functor m => (Columnar' (TableField tbl) a' -> m (Columnar' (TableField tbl) a')) -> Columnar' (TableField tbl) a -> m (Columnar' (TableField tbl) a) Source #

Eq (TableField table ty) Source # 

Methods

(==) :: TableField table ty -> TableField table ty -> Bool #

(/=) :: TableField table ty -> TableField table ty -> Bool #

Show (TableField table ty) Source # 

Methods

showsPrec :: Int -> TableField table ty -> ShowS #

show :: TableField table ty -> String #

showList :: [TableField table ty] -> ShowS #

IsString (FieldModification (TableField tbl) a) Source # 

data Exposed x Source #

newtype mainly used to inspect tho tag structure of a particular Beamable. Prevents overlapping instances in some case. Usually not used in end-user code.

Instances

fieldName :: Lens' (TableField table ty) Text Source #

Van Laarhoven lens to retrieve or set the field name from a TableField.

type TableSettings table = table (TableField table) Source #

Represents a table that contains metadata on its fields. In particular, each field of type 'Columnar f a' is transformed into 'TableField table a'. You can get or update the name of each field by using the fieldName lens.

type HaskellTable table = table Identity Source #

The regular Haskell version of the table. Equivalent to 'tbl Identity'

type TableSkeleton table = table Ignored Source #

A form of table all fields Ignored. Useful as a parameter to zipTables when you only care about one table.

data Ignored x Source #

Column tag that ignores the type.

Constructors

Ignored 

class GFieldsFulfillConstraint (c :: * -> Constraint) (exposed :: * -> *) values withconstraint where Source #

Minimal complete definition

gWithConstrainedFields

Methods

gWithConstrainedFields :: Proxy c -> Proxy exposed -> values () -> withconstraint () Source #

Instances

GFieldsFulfillConstraint c (U1 *) (U1 *) (U1 *) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (U1 *) -> U1 * () -> U1 * () Source #

FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 * R (t (Nullable Exposed))) (K1 * R (t (Nullable Identity))) (K1 * R (t (Nullable (WithConstraint c)))) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (K1 * R (t (Nullable Exposed))) -> K1 * R (t (Nullable Identity)) () -> K1 * R (t (Nullable (WithConstraint c))) () Source #

FieldsFulfillConstraint c t => GFieldsFulfillConstraint c (K1 * R (t Exposed)) (K1 * R (t Identity)) (K1 * R (t (WithConstraint c))) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (K1 * R (t Exposed)) -> K1 * R (t Identity) () -> K1 * R (t (WithConstraint c)) () Source #

c x => GFieldsFulfillConstraint c (K1 * R (Exposed x)) (K1 * R x) (K1 * R (WithConstraint c x)) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (K1 * R (Exposed x)) -> K1 * R x () -> K1 * R (WithConstraint c x) () Source #

(GFieldsFulfillConstraint c aExp a aC, GFieldsFulfillConstraint c bExp b bC) => GFieldsFulfillConstraint c ((:*:) * aExp bExp) ((:*:) * a b) ((:*:) * aC bC) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) ((* :*: aExp) bExp) -> (* :*: a) b () -> (* :*: aC) bC () Source #

GFieldsFulfillConstraint c exposed values withconstraint => GFieldsFulfillConstraint c (M1 * s m exposed) (M1 * s m values) (M1 * s m withconstraint) Source # 

Methods

gWithConstrainedFields :: Proxy (* -> Constraint) c -> Proxy (* -> *) (M1 * s m exposed) -> M1 * s m values () -> M1 * s m withconstraint () Source #

data WithConstraint (c :: * -> Constraint) x where Source #

Constructors

WithConstraint :: c x => x -> WithConstraint c x 

Instances

class TagReducesTo f f' | f -> f' where Source #

Class to automatically unwrap nested Nullables

Minimal complete definition

reduceTag

Methods

reduceTag :: Functor m => (Columnar' f' a' -> m (Columnar' f' a')) -> Columnar' f a -> m (Columnar' f a) Source #

Instances

TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # 

Methods

reduceTag :: Functor m => (Columnar' f' a' -> m (Columnar' f' a')) -> Columnar' (Nullable f) a -> m (Columnar' (Nullable f) a) Source #

TagReducesTo (TableField tbl) (TableField tbl) Source # 

Methods

reduceTag :: Functor m => (Columnar' (TableField tbl) a' -> m (Columnar' (TableField tbl) a')) -> Columnar' (TableField tbl) a -> m (Columnar' (TableField tbl) a) Source #

type family ReplaceBaseTag tag f where ... Source #

Equations

ReplaceBaseTag tag (Nullable f) = Nullable (ReplaceBaseTag tag f) 
ReplaceBaseTag tag x = tag 

Tables

class (Typeable table, Beamable table, Beamable (PrimaryKey table)) => Table (table :: (* -> *) -> *) where Source #

The big Kahuna! All beam tables implement this class.

The kind of all table types is '(* -> *) -> *'. This is because all table types are actually table type constructors. Every table type takes in another type constructor, called the column tag, and uses that constructor to instantiate the column types. See the documentation for Columnar.

This class is mostly Generic-derivable. You need only specify a type for the table's primary key and a method to extract the primary key given the table.

An example table:

data BlogPostT f = BlogPost
                 { _blogPostSlug    :: Columnar f Text
                 , _blogPostBody    :: Columnar f Text
                 , _blogPostDate    :: Columnar f UTCTime
                 , _blogPostAuthor  :: PrimaryKey AuthorT f
                 , _blogPostTagline :: Columnar f (Maybe Text)
                 , _blogPostImageGallery :: PrimaryKey ImageGalleryT (Nullable f) }
                   deriving Generic
instance Beamable BlogPostT
instance Table BlogPostT where
   data PrimaryKey BlogPostT f = BlogPostId (Columnar f Text) deriving Generic
   primaryKey = BlogPostId . _blogPostSlug
instance Beamable (PrimaryKey BlogPostT)

We can interpret this as follows:

  • The _blogPostSlug, _blogPostBody, _blogPostDate, and _blogPostTagline fields are of types Text, Text, UTCTime, and 'Maybe Text' respectfully.
  • Since _blogPostSlug, _blogPostBody, _blogPostDate, _blogPostAuthor must be provided (i.e, they cannot contain Nothing), they will be given SQL NOT NULL constraints. _blogPostTagline is declared Maybe so Nothing will be stored as NULL in the database. _blogPostImageGallery will be allowed to be empty because it uses the Nullable tag modifier.
  • blogPostAuthor references the AuthorT table (not given here) and is required.
  • blogPostImageGallery references the ImageGalleryT table (not given here), but this relation is not required (i.e., it may be Nothing. See Nullable).

Minimal complete definition

primaryKey

Associated Types

data PrimaryKey table (column :: * -> *) :: * Source #

A data type representing the types of primary keys for this table. In order to play nicely with the default deriving mechanism, this type must be an instance of Generic.

Methods

primaryKey :: table column -> PrimaryKey table column Source #

Given a table, this should return the PrimaryKey from the table. By keeping this polymorphic over column, we ensure that the primary key values come directly from the table (i.e., they can't be arbitrary constants)

class Beamable table where Source #

Provides a number of introspection routines for the beam library. Allows us to "zip" tables with different column tags together. Always instantiate an empty Beamable instance for tables, primary keys, and any type that you would like to embed within either. See the manual for more information on embedding.

Methods

zipBeamFieldsM :: Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h) Source #

zipBeamFieldsM :: (HasBeamFields table f g h, Applicative m) => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h) Source #

tblSkeleton :: TableSkeleton table Source #

tblSkeleton :: (Generic (TableSkeleton table), GTableSkeleton (Rep (TableSkeleton table))) => TableSkeleton table Source #

class Retaggable f x | x -> f where Source #

Minimal complete definition

retag

Associated Types

type Retag (tag :: (* -> *) -> * -> *) x :: * Source #

Methods

retag :: (forall a. Columnar' f a -> Columnar' (tag f) a) -> x -> Retag tag x Source #

Instances

Beamable tbl => Retaggable f (tbl f) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (tbl f) :: * Source #

Methods

retag :: (forall a. Columnar' f a -> Columnar' (tag f) a) -> tbl f -> Retag tag (tbl f) Source #

(Retaggable f a, Retaggable f b) => Retaggable f (a, b) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b) :: * Source #

Methods

retag :: (forall c. Columnar' f c -> Columnar' (tag f) c) -> (a, b) -> Retag tag (a, b) Source #

(Retaggable f a, Retaggable f b, Retaggable f c) => Retaggable f (a, b, c) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c) :: * Source #

Methods

retag :: (forall d. Columnar' f d -> Columnar' (tag f) d) -> (a, b, c) -> Retag tag (a, b, c) Source #

(Retaggable f a, Retaggable f b, Retaggable f c, Retaggable f d) => Retaggable f (a, b, c, d) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c, d) :: * Source #

Methods

retag :: (forall e. Columnar' f e -> Columnar' (tag f) e) -> (a, b, c, d) -> Retag tag (a, b, c, d) Source #

(Retaggable f a, Retaggable f b, Retaggable f c, Retaggable f d, Retaggable f e) => Retaggable f (a, b, c, d, e) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c, d, e) :: * Source #

Methods

retag :: (forall g. Columnar' f g -> Columnar' (tag f) g) -> (a, b, c, d, e) -> Retag tag (a, b, c, d, e) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f) => Retaggable f' (a, b, c, d, e, f) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c, d, e, f) :: * Source #

Methods

retag :: (forall g. Columnar' f' g -> Columnar' (tag f') g) -> (a, b, c, d, e, f) -> Retag tag (a, b, c, d, e, f) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f, Retaggable f' g) => Retaggable f' (a, b, c, d, e, f, g) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c, d, e, f, g) :: * Source #

Methods

retag :: (forall h. Columnar' f' h -> Columnar' (tag f') h) -> (a, b, c, d, e, f, g) -> Retag tag (a, b, c, d, e, f, g) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f, Retaggable f' g, Retaggable f' h) => Retaggable f' (a, b, c, d, e, f, g, h) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (a, b, c, d, e, f, g, h) :: * Source #

Methods

retag :: (forall i. Columnar' f' i -> Columnar' (tag f') i) -> (a, b, c, d, e, f, g, h) -> Retag tag (a, b, c, d, e, f, g, h) Source #

Retaggable (QGenExpr ctxt expr s) (QGenExpr ctxt expr s t) Source # 

Associated Types

type Retag (tag :: (* -> *) -> * -> *) (QGenExpr ctxt expr s t) :: * Source #

Methods

retag :: (forall a. Columnar' (QGenExpr ctxt expr s) a -> Columnar' (tag (QGenExpr ctxt expr s)) a) -> QGenExpr ctxt expr s t -> Retag tag (QGenExpr ctxt expr s t) Source #

defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table Source #

Return a TableSettings for the appropriate table type where each column has been given its default name. See the manual for information on the default naming convention.

pk :: Table t => t f -> PrimaryKey t f Source #

Synonym for primaryKey

allBeamValues :: Beamable table => (forall a. Columnar' f a -> b) -> table f -> [b] Source #

changeBeamRep :: Beamable table => (forall a. Columnar' f a -> Columnar' g a) -> table f -> table g Source #