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

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

Database.Record.Persistable

Contents

Description

This module defines proposition interfaces for database value type and record type width.

Synopsis

Specify database value type

data PersistableSqlType q Source #

Proposition to specify type q is database value type, contains null value

runPersistableNullValue :: PersistableSqlType q -> q Source #

Null value of database value type q.

unsafePersistableSqlTypeFromNull Source #

Arguments

:: q

null value of database value type q

-> PersistableSqlType q

Result proof object

Unsafely specify PersistableSqlType axiom from specified database null value which type is q.

Specify record width

type PersistableRecordWidth a = ProductConst (Sum Int) a Source #

Proposition to specify width of Haskell type a. The width is length of database value list which is converted from Haskell type a.

runPersistableRecordWidth :: PersistableRecordWidth a -> Int Source #

Get width Int value of record type a.

unsafePersistableRecordWidth Source #

Arguments

:: Int

Specify width of Haskell type a

-> PersistableRecordWidth a

Result proof object

Unsafely specify PersistableRecordWidth axiom from specified width of Haskell type a.

unsafeValueWidth :: PersistableRecordWidth a Source #

Unsafely specify PersistableRecordWidth axiom for Haskell type a which is single column type.

maybeWidth :: PersistableRecordWidth a -> PersistableRecordWidth (Maybe a) Source #

Derivation rule of PersistableRecordWidth from from Haskell type a into for Haskell type Maybe a.

Implicit derivation rules, database value type and record type width

class Eq q => PersistableType q where Source #

Interface of derivation rule for PersistableSqlType.

Minimal complete definition

persistableType

sqlNullValue :: PersistableType q => q Source #

Implicitly derived null value of database value type.

class PersistableWidth a where Source #

PersistableWidth a is implicit rule to derive PersistableRecordWidth a width proposition 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 PersistableWidth class, so you can make instance like below:

  {-# LANGUAGE DeriveGeneric #-}
  import GHC.Generics (Generic)
  --
  data Foo = Foo { ... } deriving Generic
  instance PersistableWidth Foo

Instances

PersistableWidth () Source #

Inference rule of PersistableRecordWidth for Haskell unit () type. Derive from axiom.

PersistableWidth a => PersistableWidth (Maybe a) Source #

Inference rule of PersistableRecordWidth proof object for Maybe type.

derivedWidth :: PersistableWidth a => (PersistableRecordWidth a, Int) Source #

Pass type parameter and inferred width value.

low-level interfaces

class GFieldWidthList f Source #

Generic width value list of record fields.

Minimal complete definition

gFieldWidthList

data ProductConst a b Source #

Restricted in product isomorphism record type b

Instances

getProductConst :: ProductConst a b -> a Source #

extract constant value of ProductConst.

genericFieldOffsets :: (Generic a, GFieldWidthList (Rep a)) => ProductConst (Array Int Int) a Source #

Generic offset array of record fields.