| Copyright | 2013-2017 Kei Hibino | 
|---|---|
| License | BSD3 | 
| Maintainer | ex8k.hibino@gmail.com | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.Record.Persistable
Description
This module defines interfaces between Haskell type and list of SQL type.
- data PersistableSqlType q
- runPersistableNullValue :: PersistableSqlType q -> q
- unsafePersistableSqlTypeFromNull :: q -> PersistableSqlType q
- type PersistableRecordWidth a = ProductConst (Sum Int) a
- runPersistableRecordWidth :: PersistableRecordWidth a -> Int
- unsafePersistableRecordWidth :: Int -> PersistableRecordWidth a
- unsafeValueWidth :: PersistableRecordWidth a
- (<&>) :: PersistableRecordWidth a -> PersistableRecordWidth b -> PersistableRecordWidth (a, b)
- maybeWidth :: PersistableRecordWidth a -> PersistableRecordWidth (Maybe a)
- class Eq q => PersistableType q where
- sqlNullValue :: PersistableType q => q
- class PersistableWidth a where
- derivedWidth :: PersistableWidth a => (PersistableRecordWidth a, Int)
- class GFieldWidthList f
- data ProductConst a b
- getProductConst :: ProductConst a b -> a
- genericFieldOffsets :: (Generic a, GFieldWidthList (Rep a)) => ProductConst (Array Int Int) a
Specify SQL type
data PersistableSqlType q Source #
Proof object to specify type q is SQL type
runPersistableNullValue :: PersistableSqlType q -> q Source #
Null value of SQL type q.
unsafePersistableSqlTypeFromNull Source #
Arguments
| :: q | SQL null value of SQL type  | 
| -> PersistableSqlType q | Result proof object | 
Unsafely generate PersistableSqlType proof object from specified SQL null value which type is q.
Specify record width
type PersistableRecordWidth a = ProductConst (Sum Int) a Source #
Proof object to specify width of Haskell type a
   when converting to SQL type list.
runPersistableRecordWidth :: PersistableRecordWidth a -> Int Source #
Get width Int value of record type a.
unsafePersistableRecordWidth Source #
Arguments
| :: Int | Specify width of Haskell type  | 
| -> PersistableRecordWidth a | Result proof object | 
Unsafely generate PersistableRecordWidth proof object from specified width of Haskell type a.
unsafeValueWidth :: PersistableRecordWidth a Source #
Unsafely generate PersistableRecordWidth proof object for Haskell type a which is single column type.
(<&>) :: PersistableRecordWidth a -> PersistableRecordWidth b -> PersistableRecordWidth (a, b) Source #
Derivation rule of PersistableRecordWidth for tuple (,) type.
maybeWidth :: PersistableRecordWidth a -> PersistableRecordWidth (Maybe a) Source #
Derivation rule of PersistableRecordWidth from from Haskell type a into for Haskell type Maybe a.
Inference rules for proof objects
class Eq q => PersistableType q where Source #
Interface of inference rule for PersistableSqlType proof object
Minimal complete definition
Methods
sqlNullValue :: PersistableType q => q Source #
Inferred Null value of SQL type.
class PersistableWidth a where Source #
Interface of inference rule for PersistableRecordWidth proof object
Methods
persistableWidth :: PersistableRecordWidth a Source #
persistableWidth :: (Generic a, GFieldWidthList (Rep a)) => PersistableRecordWidth a Source #
Instances
| PersistableWidth () Source # | Inference rule of  | 
| PersistableWidth a => PersistableWidth (Maybe a) Source # | Inference rule of  | 
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
| GFieldWidthList U1 Source # | |
| PersistableWidth a => GFieldWidthList (K1 i a) Source # | |
| (GFieldWidthList a, GFieldWidthList b) => GFieldWidthList ((:*:) a b) Source # | |
| GFieldWidthList a => GFieldWidthList (M1 i c a) Source # | |
data ProductConst a b Source #
Restricted in product isomorphism record type b
Instances
| Show a => Show (ProductConst a b) Source # | |
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.