beam-0.3.0.0: A type-safe SQL mapper for Haskell that doesn't use Template Haskell

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Schema

Contents

Description

Defines type classes for Tables and Databases.

All important class methods of these classes can be derived automatically using Generics and GHC's DefaultSignatures extension, but you can override any method if necessary.

To get started, see Table, Columnar, and Nullable.

Synopsis

Database Types

class Database db where Source

Minimal complete definition

Nothing

Methods

allTables :: (forall tbl. Table tbl => f tbl -> b) -> db f -> [b] Source

data GenDatabaseTable db where Source

Constructors

GenDatabaseTable :: DatabaseTable db table -> GenDatabaseTable db 

data DatabaseTable db table where Source

Constructors

DatabaseTable :: Table table => Proxy table -> Text -> DatabaseTable db table 

newtype BeamEnum a Source

Constructors

BeamEnum 

Fields

unBeamEnum :: a
 

newtype SqlValue' x Source

Constructors

SqlValue' SqlValue 

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 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
Columnar Identity (BeamEnum 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. Enum types tagged with BeamEnum, are automatically unwrapped in the simplified data structure.

Columnar (Nullable c) x = Columnar c (Maybe x)

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 (BeamEnum x) = x 
Columnar Identity x = x 
Columnar (Lenses t Identity) x = LensFor (t Identity) (Columnar Identity x) 
Columnar (Lenses t f) x = LensFor (t f) (f x) 
Columnar (Nullable c) x = Columnar c (Maybe x) 
Columnar f x = f x 

newtype Columnar' f a Source

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.

data TableField table ty Source

Metadata for a field of type ty in table.

Columnar (TableField table) ty = TableField table ty

This is used to declare tblFieldSettings in the Table class.

It is easiest to access these fields through the lenses fieldName, fieldConstraints, and fieldSettings.

data EmployeeT f = Employee
                 { _employeeId :: Columnar f AutoId
                 , _employeeDepartment :: Columnar f Text
                 , _employeeFirstName :: Columnar f Text
                 , _employeeLastName :: Columnar f Text }
                   deriving Generic

Now we can use tableConfigLenses and the TableField lenses to modify the default table configuration

Employee (LensFor employeeIdC) (LensFor employeeDepartmentC) (LensFor employeeFirstNameC) (LensFor employeeLastNameC) = tableConfigLenses

instance Table EmployeeT where
   type PrimaryKey EmployeeT f = PK f AutoId
   primaryKey = PK . _beamEmployeeId

   tblFieldSettings = defTblFieldSettings
                    & employeeFirstNameC . fieldName .~ "fname"
                    & employeeLastNameC  . fieldName .~ "lname"
                    & employeeLastNameC  . fieldSettings .~ Varchar (Just 128) -- Give it a 128 character limit

Constructors

TableField 

Fields

_fieldName :: Text

The field name

_fieldConstraints :: [SQLConstraint]

Constraints for the field (such as AutoIncrement, PrimaryKey, etc)

_fieldSettings :: FieldSettings ty

Settings for the field

Instances

type TableSettings table = table (TableField table) Source

Tables

class Typeable 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. In order for the default deriving to work, every type passed into Columnar must be an instance of FieldSchema.

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.

Even though all methods are derivable, you are free to override them. Typically, you may want to override tblFieldSettings if you want to specify options for column storage or to rename columns. See TableField for more information. You may want to use tableConfigLenses to simplify accessing tblFieldSettings.

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 Table BlogPostT where
   type PrimaryKey BlogPostT f = PK f Text
   primaryKey = PK . _blogPostSlug

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)

pkChangeRep :: (forall a. Columnar' f a -> Columnar' g a) -> PrimaryKey table f -> PrimaryKey table g Source

changeRep :: (forall a. FieldSchema a => Columnar' f a -> Columnar' g a) -> table f -> table g Source

pkAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> PrimaryKey table f -> [b] Source

fieldAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> table f -> [b] Source

tblFieldSettings :: TableSettings table Source

pkMakeSqlValues :: PrimaryKey table Identity -> PrimaryKey table SqlValue' Source

makeSqlValues :: table Identity -> table SqlValue' Source

tableFromSqlValues :: FromSqlValuesM (table Identity) Source

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

tableValuesNeeded :: Table table => Proxy table -> Int Source

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

Synonym for primaryKey

Fields

Fields

Text field

Auto-increment fields

tableConfigLenses :: (lensType ~ Lenses t (TableField t), Generic (t lensType), Generic (t (TableField t)), GTableLenses t (TableField t) (Rep (t (TableField t))) (Rep (t lensType))) => t (Lenses t (TableField t)) Source

Automatically deduce lenses for 'TableSettings table'. You can expose the lenses at global level by doing a top-level pattern match on tableConfigLenses, replacing every column in the pattern with `LensFor nameOfLensForField'.

For example,

data AuthorT f = AuthorT
               { _authorEmail     :: Columnar f Text
               , _authorFirstName :: Columnar f Text
               , _authorLastName  :: Columnar f Text }
                 deriving Generic

data BlogPostT f = BlogPost
                 { _blogPostSlug    :: Columnar f Text
                 , _blogPostBody    :: Columnar f Text
                 , _blogPostDate    :: Columnar f UTCTime
                 , _blogPostAuthor  :: ForeignKey AuthorT f
                 , _blogPostTagline :: Columnar f (Maybe Text) }
                   deriving Generic
instance Table BlogPostT where
   type PrimaryKey BlogPostT f = PK f Text
   primaryKey = PK . _blogPostSlug
instance Table AuthorT where
   type PrimaryKey AuthorT f = PK f Text
   primaryKey = PK . _authorEmail
BlogPost (LensFor blogPostSlug
         (LensFor blogPostBody)
         (LensFor blogPostDate)
         (ForeignKey (PK (LensFor blogPostAuthorEmail)))
         (LensFor blogPostTagLine) = tableConfigLenses