data-basic-0.3.0.0: A database library with a focus on ease of use, type safety and useful error messages

Safe HaskellNone
LanguageHaskell2010

Internal.Data.Basic.TH.Generator

Description

module Internal. : Data.Basic.TH.Types Description : Data types and utility function used during TH generation phase License : MIT

This module Internal.defines functions that are used to generate Template Haskell code from AST. For AST description take a look at Types.

Synopsis

Documentation

dataConstructor :: EntityInfo -> Dec Source #

Generates a data constructor for an entity

data Post = Post { _ostId     :: Key
                 , _ostName   :: Text
                 , _ostUserId :: Key } deriving (Show, Read, Generic)

fromRowInstance :: Name -> [a] -> Dec Source #

Generates a fromRow instance for a entity.

instance FromRow Post where
fromRow = Post <$> field <*> field <*> field

fromRowInstance takes a name of the entity and a list of [a], which is just used to count how many fields does the entity have - nothing else. It generates something similar shown in a code snippet above - a working FromRow instance for that datatype.

fieldOptics :: [EntityInfo] -> [Dec] Source #

Generates field optics for all entities

fieldOptic :: Text -> [Dec] Source #

Generates field optics for a column

name :: (FieldOptic "username" fun inType outType inVal outVal) => PolyOptic fun inType outType inVal outVal
name = fieldOpticProxy (Proxy :: Proxy "username")

fieldConstraint :: Constraint -> Maybe [Type] Source #

Applies basic constraint depending on sql constraint If columns is marked as primary or unique, add the Unique haskell datatype

tableField :: EntityInfo -> ColumnInfo -> Dec Source #

Generates a table field instance for a column

instance TableField Post "user_id" where
  type TableFieldType Post "user_id" = Key
  tableFieldLens = ostUserId

tableFields :: [EntityInfo] -> [Dec] Source #

Generates required table field instances for all entities

finalType :: ColumnInfo -> Type Source #

Generates final type for the sql column

initialAccessor :: EntityInfo -> [Dec] Source #

Generates initial accessor for the table

allPosts = allRows (Proxy :: Proxy "post")

fkOptics :: [ForeignKeyConstraint] -> [Dec] Source #

Generates foreign key optics

fkOptic :: ForeignKeyConstraint -> [Dec] Source #

Generates foreign key optic

author :: ForeignKeyLensProxy (Proxy "blog_post_author_fkey" -> o) => o
author = foreignKeyLens @"blog_post_author_fkey"

virtualTables :: [ForeignKeyConstraint] -> [Dec] Source #

Generates virtual table optics

virtualTable :: ForeignKeyConstraint -> [Dec] Source #

Generates virtual table optic

posts :: VirtualTable "blog_post_author_fkey" res
   => Getter' (Entity ('FromDb c) (ForeignKeyTo "blog_post_author_fkey")) res
posts = virtualTableLensProxy (Proxy :: Proxy "blog_post_author_fkey")

allConstraints :: ParseContext -> [Dec] Source #

Generates all constraint declarations from the ParseContext

uniqueConstraintInstance :: UniqueKeyConstraint -> [Dec] Source #

Generates unique key constraint instance

instance UniqueConstraint "blog_user_pkey" where
   type UniqueTable "blog_user_pkey" = User
   type UniqueFields "blog_user_pkey" = '["id"]

primaryKeyInstance :: PrimaryKeyConstraint -> [Dec] Source #

Generates primary key instance

instance PrimaryKeyConstraint "blog_user_pkey"

foreignKeyConstraint :: ForeignKeyConstraint -> Dec Source #

Generates foreign key instance

instance ForeignKeyConstraint "blog_post_author_fkey" where
type ForeignKeyFrom "blog_post_author_fkey" = Post
type ForeignKeyFromFields "blog_post_author_fkey" = '["author"]
type ForeignKeyTo "blog_post_author_fkey" = User
type ForeignKeyToFields "blog_post_author_fkey" = '["id"]

tableInstance :: ParseContext -> EntityInfo -> [Dec] Source #

Generates a table instance for an entity from a ParseContext

instance Table Post where
    type TableName Post = "blog_post"
    type TableFields Post = ["id", "name", "author"]
    type TableConstraints Post = '[]
    type TablePrimaryKey Post = 'Nothing
    type TableRequiredFields Post = ['DynamicDefault 'id, 'Required "name", 'Required "author"]

emptyEntity :: ParseContext -> EntityInfo -> [Dec] Source #

Generates a empty entity

newPost :: Entity ('Fresh ['DynamicDefault "id", 'Required "name", 'Required "author"])
newPost = Entity (Post 1 "" 1)

required :: [ColumnInfo] -> [Type] Source #

Applies Required constraint to list of columns

dynamicDefault :: [ColumnInfo] -> [Type] Source #

Applies DynamicDefault constraint to a list of columns

applyConstraint :: ColumnInfo -> ColumnConstraint -> Type -> Type Source #

Modifies column type depending on column constraints

coerceBody :: EntityInfo -> Body Source #

Generates coerce body. See NullValue why this is needed

schemaValue :: Text -> Text -> [Dec] Source #

Generated the value representing the schema that can be applied to the database