pg-store-0.2: Simple storage interface to PostgreSQL

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

Database.PostgreSQL.Store.Table

Contents

Description

 

Synopsis

Columns

data Column Source #

Desciption of a column

Constructors

Column 

Fields

data ColumnType Source #

Description of a column type

Constructors

ColumnType 

Fields

class Entity a => ColumnEntity a where Source #

Classify a type which can be used as a column in a table.

Minimal complete definition

describeColumnType

Methods

describeColumnType :: proxy a -> ColumnType Source #

Describe the column type

Instances

ColumnEntity Bool Source # 
ColumnEntity Double Source # 
ColumnEntity Float Source # 
ColumnEntity Int Source # 
ColumnEntity Int8 Source # 
ColumnEntity Int16 Source # 
ColumnEntity Int32 Source # 
ColumnEntity Int64 Source # 
ColumnEntity Integer Source # 
ColumnEntity Word Source # 
ColumnEntity Word8 Source # 
ColumnEntity Word16 Source # 
ColumnEntity Word32 Source # 
ColumnEntity Word64 Source # 
ColumnEntity ByteString Source # 
ColumnEntity ByteString Source # 
ColumnEntity Scientific Source # 
ColumnEntity String Source # 
ColumnEntity Text Source # 
ColumnEntity Value Source # 
ColumnEntity Text Source # 
ColumnEntity Natural Source # 
ColumnEntity a => ColumnEntity (Maybe a) Source # 

Methods

describeColumnType :: proxy (Maybe a) -> ColumnType Source #

Table

data Table Source #

Description of a table

Constructors

Table 

Fields

class Entity a => TableEntity a where Source #

Classify a type which can be used as a table.

Methods

describeTableType :: proxy a -> Table Source #

Describe the table type.

describeTableType :: GenericTable a => proxy a -> Table Source #

Describe the table type.

buildTableSchema :: Table -> QueryBuilder Source #

Build the SQL code which describes and creates the table.

insertColumns :: Table -> QueryBuilder Source #

Insert a comma-seperated list of the fully qualified column names of a table.

insertColumnsOn :: Table -> ByteString -> QueryBuilder Source #

Similar to insertColumns, but instead it expands the column names on an alias.

type GenericTable a = (Generic a, GTable (AnalyzeTable a)) Source #

Constraint for generic tables

describeGenericTable :: GenericTable a => proxy a -> Table Source #

Fetch the table description for a generic table type.

Helpers

data KColumns Source #

Type-level description of a record

data KTable Source #

Type-level description of a table

Constructors

TTable Symbol KColumns 

class GColumns rec where Source #

Provide the means to demote KColumns to a value.

Minimal complete definition

gDescribeColumns

Methods

gDescribeColumns :: proxy rec -> [Column] Source #

Instantiate singleton

Instances

(GColumns lhs, GColumns rhs) => GColumns (TCombine lhs rhs) Source # 

Methods

gDescribeColumns :: proxy (TCombine lhs rhs) -> [Column] Source #

(KnownSymbol name, ColumnEntity typ) => GColumns (TSelector name typ) Source # 

Methods

gDescribeColumns :: proxy (TSelector name typ) -> [Column] Source #

class GTable tbl where Source #

Provide the means to demote KTable to a value.

Minimal complete definition

gDescribeTable

Methods

gDescribeTable :: proxy tbl -> Table Source #

Instantiate singleton

Instances

(KnownSymbol name, GColumns cols) => GTable (TTable name cols) Source # 

Methods

gDescribeTable :: proxy (TTable name cols) -> Table Source #

type family AnalyzeRecordRep org (rec :: * -> *) :: KColumns where ... Source #

Check the Generic representation of a record in order to generate an instance of KColumns.

Equations

AnalyzeRecordRep org (S1 (MetaSel (Just name) m1 m2 m3) (Rec0 typ)) = TSelector name typ 
AnalyzeRecordRep org (S1 (MetaSel Nothing m1 m2 m3) a) = TypeError ((Text "Given type " :<>: ShowType org) :<>: Text " must have a single record constructor") 
AnalyzeRecordRep org (lhs :*: rhs) = TCombine (AnalyzeRecordRep org lhs) (AnalyzeRecordRep org rhs) 
AnalyzeRecordRep org U1 = TypeError ((Text "Given type " :<>: ShowType org) :<>: Text " has one constructor, therefore that constructor must have at least one field") 
AnalyzeRecordRep org other = TypeError (((Text "Given type " :<>: ShowType org) :<>: Text " has a constructor with an invalid selector") :$$: ShowType other) 

type family AnalyzeTableRep org (dat :: * -> *) :: KTable where ... Source #

Check the Generic representation of a data type in order to generate an instance of KTable.

Equations

AnalyzeTableRep org (D1 meta1 (C1 (MetaCons name f True) sel)) = TTable name (AnalyzeRecordRep org sel) 
AnalyzeTableRep org (D1 meta other) = TypeError ((Text "Given type " :<>: ShowType org) :<>: Text " must have a single record constructor") 
AnalyzeTableRep org other = TypeError (((Text "Given type " :<>: ShowType org) :<>: Text " is not a valid data type") :$$: ShowType other) 

type AnalyzeTable a = AnalyzeTableRep a (Rep a) Source #

Analyzes a type in order to retrieve its KTable representation.