pg-store-0.5.0: Simple storage interface to PostgreSQL

Copyright(c) Ole Krüger 2016
LicenseBSD3
MaintainerOle Krüger <ole@vprsm.de>
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Store.Entity

Contents

Description

 

Synopsis

Result and query entity

class KnownNat (Width a) => Entity a where Source #

An entity that is used as a parameter or result of a query.

Associated Types

type Width a :: Nat Source #

Number of values of which the entity consists

Methods

genEntity :: QueryGenerator a Source #

Embed the entity into the query.

genEntity :: (Generic a, GEntity (Rep a)) => QueryGenerator a Source #

Embed the entity into the query.

parseEntity :: RowParser (Width a) a Source #

Retrieve an instance of a from the result set.

parseEntity :: (Generic a, GEntity (Rep a), Width a ~ GEntityWidth (Rep a)) => RowParser (Width a) a Source #

Retrieve an instance of a from the result set.

Instances

Entity Bool Source #
boolean
Entity Double Source #

Any floating-point number

Entity Float Source #

Any floating-point number

Entity Int Source #

Any integer

Entity Int8 Source #

Any integer

Entity Int16 Source #

Any integer

Entity Int32 Source #

Any integer

Entity Int64 Source #

Any integer

Entity Integer Source #

Any integer

Entity Word Source #

Any unsigned integer

Entity Word8 Source #

Any unsigned integer

Entity Word16 Source #

Any unsigned integer

Entity Word32 Source #

Any unsigned integer

Entity Word64 Source #

Any unsigned integer

Entity ByteString Source #

bytea - byte array encoded in hex format

Entity ByteString Source #

bytea - byte array encoded in hex format

Entity Scientific Source #

Any numeric type

Entity String Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Text Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Value Source #

json or jsonb

Entity Text Source #

char, varchar or text - UTF-8 encoded; does not allow NULL characters

Entity Natural Source #

Any unsigned integer

Entity a => Entity (Maybe a) Source #

A value which may be NULL.

Associated Types

type Width (Maybe a) :: Nat Source #

GenericEntity (a, b) => Entity (a, b) Source #

Chain of 2 entities

Associated Types

type Width (a, b) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b) Source #

parseEntity :: RowParser (Width (a, b)) (a, b) Source #

GenericEntity (a, b, c) => Entity (a, b, c) Source #

Chain of 3 entities

Associated Types

type Width (a, b, c) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c) Source #

parseEntity :: RowParser (Width (a, b, c)) (a, b, c) Source #

GenericEntity (a, b, c, d) => Entity (a, b, c, d) Source #

Chain of 4 entities

Associated Types

type Width (a, b, c, d) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d) Source #

parseEntity :: RowParser (Width (a, b, c, d)) (a, b, c, d) Source #

GenericEntity (a, b, c, d, e) => Entity (a, b, c, d, e) Source #

Chain of 5 entities

Associated Types

type Width (a, b, c, d, e) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e) Source #

parseEntity :: RowParser (Width (a, b, c, d, e)) (a, b, c, d, e) Source #

GenericEntity (a, b, c, d, e, f) => Entity (a, b, c, d, e, f) Source #

Chain of 6 entities

Associated Types

type Width (a, b, c, d, e, f) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e, f) Source #

parseEntity :: RowParser (Width (a, b, c, d, e, f)) (a, b, c, d, e, f) Source #

GenericEntity (a, b, c, d, e, f, g) => Entity (a, b, c, d, e, f, g) Source #

Chain of 7 entities

Associated Types

type Width (a, b, c, d, e, f, g) :: Nat Source #

Methods

genEntity :: QueryGenerator (a, b, c, d, e, f, g) Source #

parseEntity :: RowParser (Width (a, b, c, d, e, f, g)) (a, b, c, d, e, f, g) Source #

embedEntity :: Entity e => e -> QueryGenerator a Source #

Embed an entity into the query.

param0 :: Entity r => QueryGenerator (Tuple (r ': ts)) Source #

Parameter entity at index 0

param1 :: Entity r => QueryGenerator (Tuple (t0 ': (r ': ts))) Source #

Parameter entity at index 1

param2 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (r ': ts)))) Source #

Parameter entity at index 2

param3 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (r ': ts))))) Source #

Parameter entity at index 3

param4 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (r ': ts)))))) Source #

Parameter entity at index 4

param5 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (t4 ': (r ': ts))))))) Source #

Parameter entity at index 5

param6 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (t4 ': (t5 ': (r ': ts)))))))) Source #

Parameter entity at index 6

param7 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (t4 ': (t5 ': (t6 ': (r ': ts))))))))) Source #

Parameter entity at index 7

param8 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (t4 ': (t5 ': (t6 ': (t7 ': (r ': ts)))))))))) Source #

Parameter entity at index 8

param9 :: Entity r => QueryGenerator (Tuple (t0 ': (t1 ': (t2 ': (t3 ': (t4 ': (t5 ': (t6 ': (t7 ': (t8 ': (r ': ts))))))))))) Source #

Parameter entity at index 9

genGeneric :: (Generic a, GEntity (Rep a)) => QueryGenerator a Source #

Generic QueryGenerator for an entity.

parseGeneric :: (Generic a, GEntity (Rep a)) => RowParser (GEntityWidth (Rep a)) a Source #

Generic RowParser for an entity.

Helpers

class KnownNat (GRecordWidth rec) => GEntityRecord rec where Source #

Generic record entity

Minimal complete definition

gEmbedRecord, gParseRecord

Associated Types

type GRecordWidth rec :: Nat Source #

Instances

(GEntityRecord lhs, GEntityRecord rhs, KnownNat ((+) (GRecordWidth lhs) (GRecordWidth rhs))) => GEntityRecord (TCombine lhs rhs) Source # 

Associated Types

type GRecordWidth (TCombine lhs rhs :: KRecord) :: Nat Source #

Entity typ => GEntityRecord (TSingle meta typ) Source # 

Associated Types

type GRecordWidth (TSingle meta typ :: KRecord) :: Nat Source #

class KnownNat (GEntityWidth dat) => GEntity dat where Source #

Generic entity

Minimal complete definition

gEmbedEntity, gParseEntity

Associated Types

type GEntityWidth dat :: Nat Source #

Instances

GEntityEnum enum => GEntity (TFlatSum d enum) Source # 
GEntityRecord rec => GEntity (TRecord d c rec) Source # 

Associated Types

type GEntityWidth (TRecord d c rec :: KDataType) :: Nat Source #

type GenericEntity a = (Generic a, GEntity (Rep a)) Source #

This is required if you want to use the default implementations of genEntityor parseEntity with polymorphic data types.