persistable-record-0.6.0.6: Binding between SQL database values and haskell records.
Copyright2013-2017 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Record.Persistable

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.

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

Minimal complete definition

Nothing

Instances

Instances details
PersistableWidth Int16 Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth Int32 Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth Int64 Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth Int8 Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth String Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth () Source #

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

Instance details

Defined in Database.Record.Persistable

PersistableWidth Bool Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth Char Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth Int Source # 
Instance details

Defined in Database.Record.Instances

PersistableWidth a => PersistableWidth (Maybe a) Source #

Inference rule of PersistableRecordWidth proof object for Maybe type.

Instance details

Defined in Database.Record.Persistable

(PersistableWidth a, PersistableWidth b) => PersistableWidth (a, b) Source # 
Instance details

Defined in Database.Record.TupleInstances

(PersistableWidth a, PersistableWidth b, PersistableWidth c) => PersistableWidth (a, b, c) Source # 
Instance details

Defined in Database.Record.TupleInstances

(PersistableWidth a, PersistableWidth b, PersistableWidth c, PersistableWidth d) => PersistableWidth (a, b, c, d) Source # 
Instance details

Defined in Database.Record.TupleInstances

(PersistableWidth a, PersistableWidth b, PersistableWidth c, PersistableWidth d, PersistableWidth e) => PersistableWidth (a, b, c, d, e) Source # 
Instance details

Defined in Database.Record.TupleInstances

(PersistableWidth a, PersistableWidth b, PersistableWidth c, PersistableWidth d, PersistableWidth e, PersistableWidth f) => PersistableWidth (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Record.TupleInstances

Methods

persistableWidth :: PersistableRecordWidth (a, b, c, d, e, f) Source #

(PersistableWidth a, PersistableWidth b, PersistableWidth c, PersistableWidth d, PersistableWidth e, PersistableWidth f, PersistableWidth g) => PersistableWidth (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Record.TupleInstances

Methods

persistableWidth :: PersistableRecordWidth (a, b, c, d, e, f, g) Source #

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

Instances

Instances details
GFieldWidthList (U1 :: Type -> Type) Source # 
Instance details

Defined in Database.Record.Persistable

(GFieldWidthList a, GFieldWidthList b) => GFieldWidthList (a :*: b) Source # 
Instance details

Defined in Database.Record.Persistable

Methods

gFieldWidthList :: ProductConst (DList Int) ((a :*: b) a0)

PersistableWidth a => GFieldWidthList (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Database.Record.Persistable

Methods

gFieldWidthList :: ProductConst (DList Int) (K1 i a a0)

GFieldWidthList a => GFieldWidthList (M1 i c a) Source # 
Instance details

Defined in Database.Record.Persistable

Methods

gFieldWidthList :: ProductConst (DList Int) (M1 i c a a0)

data ProductConst a b Source #

Restricted in product isomorphism record type b

Instances

Instances details
Monoid a => ProductIsoApplicative (ProductConst a) Source # 
Instance details

Defined in Database.Record.Persistable

Methods

pureP :: ProductConstructor a0 => a0 -> ProductConst a a0 #

(|*|) :: ProductConst a (a0 -> b) -> ProductConst a a0 -> ProductConst a b #

ProductIsoFunctor (ProductConst a) Source # 
Instance details

Defined in Database.Record.Persistable

Methods

(|$|) :: ProductConstructor (a0 -> b) => (a0 -> b) -> ProductConst a a0 -> ProductConst a b #

Show a => Show (ProductConst a b) Source # 
Instance details

Defined in Database.Record.Persistable

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.