beam-th-0.2.0.0: Template Haskell utilities for beam

Safe HaskellNone
LanguageHaskell2010

Database.Beam.TH

Description

Functions to derive common boilerplate code when writing table types for the beam library. Only use them if you what you're doing.

The following GHC extensions have to be enabled in order to make the generated code typecheck:

{-# LANGUAGE TemplateHaskell, KindSignatures, StandaloneDeriving, TypeFamilies, TypeSynonymInstances, FlexibleInstances, DeriveGeneric #-}

Synopsis

Documentation

makeTable Source #

Arguments

:: Name

The table type name. It should end with "T", otherwise the derived names will be bogus.

-> Name

The primary key field name

-> DecsQ 

Derives boilerplate code for beam table types.

makeTable is equivalent to makeTable' except that makeTable takes a second argument, the name of the primary key, while makeTable' automatically makes the first field of the record the primary key.

makeTable ''UserT 'userNumber == makeTable' ''UserT

makeTable' Source #

Arguments

:: Name

The table type name. It should end with "T", otherwise the derived names will be bogus.

-> DecsQ 

Derives boilerplate code for beam table types.

>>> :set -XTemplateHaskell
>>> data UserT f = User { userNumber :: Columnar f Int }
>>> putStrLn $(stringE . pprint =<< makeTable' ''UserT)
type User = UserT Data.Functor.Identity.Identity
deriving instance GHC.Show.Show User
instance Database.Beam.Schema.Tables.Table UserT
    where data Database.Beam.Schema.Tables.PrimaryKey UserT f_0
              = UserId (Database.Beam.Schema.Tables.Columnar f_0 GHC.Types.Int)
              deriving GHC.Generics.Generic
          Database.Beam.Schema.Tables.primaryKey x_1 = UserId (Ghci4.userNumber x_1)
type UserId (f_2 :: * ->
                    *) = Database.Beam.Schema.Tables.PrimaryKey UserT f_2
type UserId' = UserId Data.Functor.Identity.Identity
deriving instance GHC.Show.Show UserId'
userNumberC :: Lens.Micro.Type.Lens' (UserT (Database.Beam.Schema.Tables.TableField UserT))
                                     (Database.Beam.Schema.Tables.TableField UserT _)
User (Database.Beam.Schema.Tables.LensFor userNumberC) = Database.Beam.Schema.Lenses.tableConfigLenses

Note: While the above example actually is a valid doctest, due to variable renaming and the pretty printer having a line break deficit it looks rather confusing. Therefore, consider the following reformatted but otherwise equivalent example:

type User = UserT Identity
deriving instance Show User
instance Table UserT where
    data PrimaryKey UserT f = UserId (Columnar f Int) deriving Generic
    primaryKey = UserId . userNumber
type UserId f = PrimaryKey UserT f
type UserId' = UserId Identity
deriving instance Show UserId'
userNumberC :: Lens' (UserT (TableField UserT)) (TableField UserT Int)
User (LensFor userNumberC) = tableConfigLenses

Note that the UserId type synonym is very useful when refering to other tables in fields. Consider this: data BlogPostT f = BlogPost { blogPostId :: Columnar f Int, blogPostAuthor :: UserId f }

makeTable is equivalent to makeTable' except that makeTable takes a second argument, the name of the primary key, while makeTable' automatically makes the first field of the record the primary key.

makeTable ''UserT 'userNumber == makeTable' ''UserT