opaleye-0.9.5.1: An SQL-generating DSL targeting PostgreSQL
Safe HaskellSafe-Inferred
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 field 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 field 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 fields 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 field you must give it a Maybe (Field SqlInt4). If you provide Nothing then the field 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 fields 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 field 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 SqlInt4) (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" })

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 :: InferrableTableField w n r => String -> TableFields w (Field_ n r) 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 (Field_ n a)) (Field_ n a) Source #

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

requiredTableField :: String -> TableFields (Field_ n a) (Field_ n a) Source #

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

class InferrableTableField w n r | w -> n, w -> r Source #

You should not define your own instances of InferrableTableField.

Minimal complete definition

tableField

Instances

Instances details
InferrableTableField (Maybe (Field_ n r)) n r Source #

Equivalent to defining the column with optionalTableField. If the write type is Maybe (Field_ n r) (i.e. DEFAULT can be written to it) then the write type is Field_ n r.

Instance details

Defined in Opaleye.Internal.Table

Methods

tableField :: String -> TableFields (Maybe (Field_ n r)) (Field_ n r) Source #

InferrableTableField (Field_ n r) n r Source #

Equivalent to defining the column with requiredTableField. If the write type is Field_ n r then the read type is also Field_ n r.

Instance details

Defined in Opaleye.Internal.Table

Methods

tableField :: String -> TableFields (Field_ n r) (Field_ n r) Source #

Selecting from tables

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

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

data TableFields writeColumns viewColumns Source #

Instances

Instances details
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') #

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 #

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 #

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 #

Explicit versions

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

Deprecated versions

readOnlyTableField :: String -> TableFields () (Field_ n a) Source #

Don't use readOnlyTableField. It will be formally deprecated in a future version. It is broken for updates because it always updates its field with DEFAULT which is very unlikely to be what you want! For more details see https://github.com/tomjaguarpaw/haskell-opaleye/issues/447#issuecomment-685617841.