generic-persistence-0.7.0.1: Database persistence using generics
Safe HaskellSafe-Inferred
LanguageGHC2021

Database.GP.SqlGenerator

Synopsis

Documentation

insertStmtFor :: forall a. Entity a => String Source #

This module defines some basic SQL statements for Record Data Types that are instances of Entity. The SQL statements are generated using Haskell generics to provide compile time reflection capabilities.

A function that returns an SQL insert statement for an entity. Type a must be an instance of Data. The function will use the field names of the data type to generate the column names in the insert statement. The values of the fields will be used as the values in the insert statement. Output example: INSERT INTO Person (id, name, age, address) VALUES (123456, Alice, 25, "123 Main St");

updateStmtFor :: forall a. Entity a => String Source #

A function that returns an SQL update statement for an entity. Type a must be an instance of Entity.

upsertStmtFor :: forall a. Entity a => String Source #

selectFromStmt :: forall a. Entity a => WhereClauseExpr -> String Source #

A function that returns an SQL select statement for an entity. Type a must be an instance of Entity. The function takes a where clause expression as parameter. This expression is used to filter the result set.

countStmtFor :: forall a. Entity a => WhereClauseExpr -> String Source #

A function that returns an SQL count statement for an entity. Type a must be an instance of Entity. The function takes a where clause expression as parameter. This expression is used to filter the result set.

deleteStmtFor :: forall a. Entity a => String Source #

A function that returns an SQL delete statement for an entity. Type a must be an instance of Entity.

createTableStmtFor :: forall a. Entity a => ColumnTypeMapping -> String Source #

A function that returns an SQL create table statement for an entity type. Type a must be an instance of Entity.

dropTableStmtFor :: forall a. Entity a => String Source #

This function generates a DROP TABLE statement for an entity type.

columnTypeFor :: forall a. Entity a => ColumnTypeMapping -> String -> String Source #

A function that returns the column type for a field of an entity. The function takes a column type mapping function as parameter. This function is used to map Haskell field types to SQL column types.

in' :: Convertible b SqlValue => Field -> [b] -> WhereClauseExpr infixl 4 Source #

data SortOrder Source #

Constructors

ASC 
DESC 

Instances

Instances details
Show SortOrder Source # 
Instance details

Defined in Database.GP.Query

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Ord a => Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Database Source #

An enumeration of the supported database types.

Constructors

Postgres 
SQLite 

defaultSqliteMapping :: ColumnTypeMapping Source #

The default mapping for SQLite databases. This mapping is used when no custom mapping is provided.

defaultPostgresMapping :: ColumnTypeMapping Source #

The default mapping for Postgres databases. This mapping is used when no custom mapping is provided.

type ColumnTypeMapping = String -> String Source #

A type alias for mapping a Haskell field type to a SQL column type. this type can be used to define custom mappings for field types.