persistable-record-0.5.2.2: Binding between SQL database values and haskell records.

Copyright2013-2017 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellSafe
LanguageHaskell2010

Database.Record.ToSql

Contents

Description

This module defines interfaces from Haskell type into list of database value type.

Synopsis

Conversion from record type into list of database value type

type ToSqlM q a = Writer (DList q) a Source #

Context type to convert into database value list.

data RecordToSql q a Source #

RecordToSql q a is data-type wrapping function to convert from Haskell type a into list of database value type (to send to database) [q].

This structure is similar to printer. While running RecordToSql behavior is the same as list printer. which appends list of database value type [q] stream.

runFromRecord Source #

Arguments

:: RecordToSql q a

printer function object which has capability to convert

-> a

Haskell type

-> [q]

list of database value

Run RecordToSql printer function object. Convert from Haskell type a into list of database value type [q].

createRecordToSql Source #

Arguments

:: (a -> [q])

Convert function body

-> RecordToSql q a

Result printer function object

Axiom of RecordToSql for database value type q and Haksell type a.

(<&>) :: RecordToSql q a -> RecordToSql q b -> RecordToSql q (a, b) infixl 4 Source #

Derivation rule of RecordToSql printer function object for Haskell tuple (,) type.

Derivation rules of RecordToSql conversion

class PersistableWidth a => ToSql q a where Source #

ToSql q a is implicit rule to derive RecordToSql q a record printer function for type a.

Generic programming (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#generic-programming) with default signature is available for ToSql class, so you can make instance like below:

  {-# LANGUAGE DeriveGeneric #-}
  import GHC.Generics (Generic)
  import Database.HDBC (SqlValue)
  --
  data Foo = Foo { ... } deriving Generic
  instance ToSql SqlValue Foo

To make instances of ToSql manually, ToSql q a and RecordToSql 'q a are composable with monadic context. When, you have data constructor and objects like below.

  data MyRecord = MyRecord Foo Bar Baz
  instance ToSql SqlValue Foo where
    ...
  instance ToSql SqlValue Bar where
    ...
  instance ToSql SqlValue Baz where
    ...

You can get composed ToSql implicit rule like below.

  instance ToSql SqlValue MyRecord where
    recordToSql =
    recordToSql = wrapToSql $ \ (MyRecord x y z) -> do
      putRecord x
      putRecord y
      putRecord z

Methods

recordToSql :: RecordToSql q a Source #

Derived RecordToSql printer function object.

recordToSql :: (Generic a, GToSql q (Rep a)) => RecordToSql q a Source #

Derived RecordToSql printer function object.

Instances

ToSql q () Source #

Implicit derivation rule of RecordToSql printer function object which can convert from Haskell unit () type into empty list of database value type [q].

(PersistableType q, ToSql q a) => ToSql q (Maybe a) Source #

Implicit derivation rule of RecordToSql printer function object which can convert from Haskell Maybe type into list of database value type [q].

putRecord :: ToSql q a => a -> ToSqlM q () Source #

Run implicit RecordToSql printer function object. Context to convert haskell record type a into lib of database value type [q].

putEmpty :: () -> ToSqlM q () Source #

Run RecordToSql empty printer.

fromRecord :: ToSql q a => a -> [q] Source #

Run implicit RecordToSql printer function object. Convert from haskell type a into list of database value type [q].

wrapToSql :: (a -> ToSqlM q ()) -> RecordToSql q a Source #

Finalize RecordToSql record printer.

valueRecordToSql :: (a -> q) -> RecordToSql q a Source #

Derivation rule of RecordToSql printer function object for value convert function.

Make parameter list for updating with key

updateValuesByUnique Source #

Arguments

:: ToSql q ra 
=> KeyConstraint Unique ra

Unique key table constraint printer function object.

-> ra 
-> [q] 

Convert like updateValuesByUnique' using implicit RecordToSql printer function object.

updateValuesByPrimary :: (HasKeyConstraint Primary ra, ToSql q ra) => ra -> [q] Source #

Convert like updateValuesByUnique' using implicit RecordToSql and ColumnConstraint.

updateValuesByUnique' Source #

Arguments

:: RecordToSql q ra 
-> KeyConstraint Unique ra

Unique key table constraint printer function object.

-> ra 
-> [q] 

Convert from Haskell type ra into database value q list expected by update form like

  UPDATE table SET c0 = ?, c1 = ?, c2 = ? ... WHERE key0 = ? AND key1 = ? AND key2 = ? ...

using RecordToSql printer function object.

untypedUpdateValuesIndex Source #

Arguments

:: [Int]

Key indexes

-> Int

Record width

-> [Int]

Indexes to update other than key

Make untyped indexes to update column from key indexes and record width. Expected by update form like

  UPDATE table SET c0 = ?, c1 = ?, c2 = ? ... WHERE key0 = ? AND key1 = ? AND key2 = ? ...
 

unsafeUpdateValuesWithIndexes :: RecordToSql q ra -> [Int] -> ra -> [q] Source #

Unsafely specify key indexes to convert from Haskell type ra into database value q list expected by update form like

  UPDATE table SET c0 = ?, c1 = ?, c2 = ? ... WHERE key0 = ? AND key1 = ? AND key2 = ? ...

using RecordToSql printer function object.