opaleye-0.7.2.0: An SQL-generating DSL targeting PostgreSQL
Safe HaskellNone
LanguageHaskell2010

Opaleye.Table

Description

Table fields can be required or optional and, independently, nullable or non-nullable.

A required non-nullable SqlInt4 (for example) is defined with requiredTableField and gives rise to a

TableFields (Field SqlInt4) (Field SqlInt4)

The leftmost argument is the type of writes. When you insert or update into this column you must give it a Field SqlInt4 (which you can define with sqlInt4 :: Int -> Field SqlInt4).

A required nullable SqlInt4 is defined with requiredTableField and gives rise to a

TableFields (FieldNullable SqlInt4) (FieldNullable SqlInt4)

When you insert or update into this column you must give it a FieldNullable SqlInt4, which you can define either with sqlInt4 and toNullable :: Field a -> FieldNullable a, or with null :: FieldNullable a.

An optional non-nullable SqlInt4 is defined with optionalTableField and gives rise to a

TableFields (Maybe (Field SqlInt4)) (Field SqlInt4)

Optional columns are those that can be omitted on writes, such as those that have DEFAULTs or those that are SERIAL. When you insert or update into this column you must give it a Maybe (Field SqlInt4). If you provide Nothing then the column will be omitted from the query and the default value will be used. Otherwise you have to provide a Just containing a Field SqlInt4.

An optional nullable SqlInt4 is defined with optionalTableField and gives rise to a

TableFields (Maybe (FieldNullable SqlInt4)) (FieldNullable SqlInt4)

Optional columns are those that can be omitted on writes, such as those that have DEFAULTs or those that are SERIAL. When you insert or update into this column you must give it a Maybe (FieldNullable SqlInt4). If you provide Nothing then the default value will be used. Otherwise you have to provide a Just containing a FieldNullable SqlInt4 (which can be null).

Synopsis

Defining tables

table Source #

Arguments

:: String

Table name

-> TableFields writeFields viewFields 
-> Table writeFields viewFields 

Define a table with an unqualified name.

tableWithSchema Source #

Arguments

:: String

Schema name

-> String

Table name

-> TableFields writeFields viewFields 
-> Table writeFields viewFields 

Define a table with a qualified name.

data Table writeFields viewFields Source #

Define a table as follows, where "id", "color", "location", "quantity" and "radius" are the table's fields in Postgres and the types are given in the type signature. The id field is an autoincrementing field (i.e. optional for writes).

data Widget a b c d e = Widget { wid      :: a
                               , color    :: b
                               , location :: c
                               , quantity :: d
                               , radius   :: e }

$(makeAdaptorAndInstance "pWidget" ''Widget)

widgetTable :: Table (Widget (Maybe (Field SqlInt4)) (Field SqlText) (Field SqlText)
                             (Field SqlInt4) (Field SqlFloat8))
                     (Widget (Field SqlText) (Field SqlText) (Field SqlText)
                             (Field SqlInt4) (Field SqlFloat8))
widgetTable = table "widgetTable"
                     (pWidget Widget { wid      = tableField "id"
                                     , color    = tableField "color"
                                     , location = tableField "location"
                                     , quantity = tableField "quantity"
                                     , radius   = tableField "radius" })

The constructors of Table are internal only and will be removed in version 0.8.

Instances

Instances details
Profunctor Table Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

dimap :: (a -> b) -> (c -> d) -> Table b c -> Table a d #

lmap :: (a -> b) -> Table b c -> Table a c #

rmap :: (b -> c) -> Table a b -> Table a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Table a b -> Table a c #

(.#) :: forall a b c q. Coercible b a => Table b c -> q a b -> Table a c #

Functor (Table a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

fmap :: (a0 -> b) -> Table a a0 -> Table a b #

(<$) :: a0 -> Table a b -> Table a a0 #

tableField :: TableColumn writeType sqlType => String -> TableFields writeType (Column sqlType) Source #

Infer either a required (requiredTableField) or optional (optionalTableField) field depending on the write type. It's generally more convenient to use this than required or optional but you do have to provide a type signature instead.

optionalTableField :: String -> TableFields (Maybe (Column a)) (Column a) Source #

optionalTableField is for fields that you can omit on writes, such as fields which have defaults or which are SERIAL.

readOnlyTableField :: String -> TableFields () (Column a) Source #

readOnlyTableField is for fields that you must omit on writes, such as SERIAL fields intended to auto-increment only.

requiredTableField :: String -> TableFields (Column a) (Column a) Source #

requiredTableField is for fields which are not optional. You must provide them on writes.

Selecting from tables

selectTable Source #

Arguments

:: Default Unpackspec fields fields 
=> Table a fields 
-> Select fields 

Example type specialization:

selectTable :: Table w (Field a, Field b)
            -> Select (Field a, Field b)

Assuming the makeAdaptorAndInstance splice has been run for the product type Foo:

selectTable :: Table w (Foo (Field a) (Field b) (Field c))
            -> Select (Foo (Field a) (Field b) (Field c))

Data types

type TableColumns = TableFields Source #

Deprecated: Use TableFields instead. TableColumns will be removed in version 0.8.

data TableFields writeColumns viewColumns Source #

Instances

Instances details
Profunctor TableFields Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

dimap :: (a -> b) -> (c -> d) -> TableFields b c -> TableFields a d #

lmap :: (a -> b) -> TableFields b c -> TableFields a c #

rmap :: (b -> c) -> TableFields a b -> TableFields a c #

(#.) :: forall a b c q. Coercible c b => q b c -> TableFields a b -> TableFields a c #

(.#) :: forall a b c q. Coercible b a => TableFields b c -> q a b -> TableFields a c #

ProductProfunctor TableFields Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

purePP :: b -> TableFields a b #

(****) :: TableFields a (b -> c) -> TableFields a b -> TableFields a c #

empty :: TableFields () () #

(***!) :: TableFields a b -> TableFields a' b' -> TableFields (a, a') (b, b') #

Functor (TableFields a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

fmap :: (a0 -> b) -> TableFields a a0 -> TableFields a b #

(<$) :: a0 -> TableFields a b -> TableFields a a0 #

Applicative (TableFields a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

pure :: a0 -> TableFields a a0 #

(<*>) :: TableFields a (a0 -> b) -> TableFields a a0 -> TableFields a b #

liftA2 :: (a0 -> b -> c) -> TableFields a a0 -> TableFields a b -> TableFields a c #

(*>) :: TableFields a a0 -> TableFields a b -> TableFields a b #

(<*) :: TableFields a a0 -> TableFields a b -> TableFields a a0 #

Explicit versions

selectTableExplicit Source #

Arguments

:: Unpackspec tablefields fields 
-> Table a tablefields 
-> Select fields 

Deprecated

optional :: String -> TableFields (Maybe (Column a)) (Column a) Source #

Deprecated: Use optionalTableField instead. Will be removed in version 0.8.

readOnly :: String -> TableFields () (Column a) Source #

Deprecated: Use readOnlyTableField instead. Will be removed in version 0.8.

required :: String -> TableFields (Column a) (Column a) Source #

Deprecated: Use requiredTableField instead. Will be removed in version 0.8.

tableColumn :: TableColumn writeType sqlType => String -> TableFields writeType (Column sqlType) Source #

Deprecated: Use tableField instead. Will be removed in 0.8.

data View columns Source #

Deprecated: Internal only. Do not use. View will be removed in version 0.8.

data Writer columns dummy Source #

Deprecated: Internal only. Do not use. Writer will be removed in 0.8.

Instances

Instances details
Profunctor Writer Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

dimap :: (a -> b) -> (c -> d) -> Writer b c -> Writer a d #

lmap :: (a -> b) -> Writer b c -> Writer a c #

rmap :: (b -> c) -> Writer a b -> Writer a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Writer a b -> Writer a c #

(.#) :: forall a b c q. Coercible b a => Writer b c -> q a b -> Writer a c #

ProductProfunctor Writer Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

purePP :: b -> Writer a b #

(****) :: Writer a (b -> c) -> Writer a b -> Writer a c #

empty :: Writer () () #

(***!) :: Writer a b -> Writer a' b' -> Writer (a, a') (b, b') #

Functor (Writer a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

fmap :: (a0 -> b) -> Writer a a0 -> Writer a b #

(<$) :: a0 -> Writer a b -> Writer a a0 #

Applicative (Writer a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

pure :: a0 -> Writer a a0 #

(<*>) :: Writer a (a0 -> b) -> Writer a a0 -> Writer a b #

liftA2 :: (a0 -> b -> c) -> Writer a a0 -> Writer a b -> Writer a c #

(*>) :: Writer a a0 -> Writer a b -> Writer a b #

(<*) :: Writer a a0 -> Writer a b -> Writer a a0 #

data Table writeFields viewFields Source #

Define a table as follows, where "id", "color", "location", "quantity" and "radius" are the table's fields in Postgres and the types are given in the type signature. The id field is an autoincrementing field (i.e. optional for writes).

data Widget a b c d e = Widget { wid      :: a
                               , color    :: b
                               , location :: c
                               , quantity :: d
                               , radius   :: e }

$(makeAdaptorAndInstance "pWidget" ''Widget)

widgetTable :: Table (Widget (Maybe (Field SqlInt4)) (Field SqlText) (Field SqlText)
                             (Field SqlInt4) (Field SqlFloat8))
                     (Widget (Field SqlText) (Field SqlText) (Field SqlText)
                             (Field SqlInt4) (Field SqlFloat8))
widgetTable = table "widgetTable"
                     (pWidget Widget { wid      = tableField "id"
                                     , color    = tableField "color"
                                     , location = tableField "location"
                                     , quantity = tableField "quantity"
                                     , radius   = tableField "radius" })

The constructors of Table are internal only and will be removed in version 0.8.

Constructors

Table String (TableFields writeFields viewFields)

For unqualified table names. Do not use the constructor. It is considered deprecated and will be removed in version 0.8.

TableWithSchema String String (TableFields writeFields viewFields)

Schema name, table name, table properties. Do not use the constructor. It is considered deprecated and will be removed in version 0.8.

Instances

Instances details
Profunctor Table Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

dimap :: (a -> b) -> (c -> d) -> Table b c -> Table a d #

lmap :: (a -> b) -> Table b c -> Table a c #

rmap :: (b -> c) -> Table a b -> Table a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Table a b -> Table a c #

(.#) :: forall a b c q. Coercible b a => Table b c -> q a b -> Table a c #

Functor (Table a) Source # 
Instance details

Defined in Opaleye.Internal.Table

Methods

fmap :: (a0 -> b) -> Table a a0 -> Table a b #

(<$) :: a0 -> Table a b -> Table a a0 #

queryTable :: Default Unpackspec fields fields => Table a fields -> Select fields Source #

Deprecated: Use selectTable instead. Will be removed in version 0.8.

queryTableExplicit :: Unpackspec tablefields fields -> Table a tablefields -> Select fields Source #

Deprecated: Use selectTableExplicit instead. Will be removed in version 0.8.