Safe Haskell | None |
---|---|
Language | Haskell2010 |
A DSL for declaration of result decoders.
- data Result a
- unit :: Result ()
- rowsAffected :: Result Int64
- singleRow :: Row a -> Result a
- rowMaybe :: Row a -> Result (Maybe a)
- rowVector :: Row a -> Result (Vector a)
- rowList :: Row a -> Result [a]
- foldlRows :: (a -> b -> a) -> a -> Row b -> Result a
- foldrRows :: (b -> a -> a) -> a -> Row b -> Result a
- data Row a
- column :: Value a -> Row a
- nullableColumn :: Value a -> Row (Maybe a)
- data Value a
- bool :: Value Bool
- int2 :: Value Int16
- int4 :: Value Int32
- int8 :: Value Int64
- float4 :: Value Float
- float8 :: Value Double
- numeric :: Value Scientific
- char :: Value Char
- text :: Value Text
- bytea :: Value ByteString
- date :: Value Day
- timestamp :: Value LocalTime
- timestamptz :: Value UTCTime
- time :: Value TimeOfDay
- timetz :: Value (TimeOfDay, TimeZone)
- interval :: Value DiffTime
- uuid :: Value UUID
- inet :: Value (NetAddr IP)
- json :: Value Value
- jsonBytes :: (ByteString -> Either Text a) -> Value a
- jsonb :: Value Value
- jsonbBytes :: (ByteString -> Either Text a) -> Value a
- array :: Array a -> Value a
- composite :: Composite a -> Value a
- hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a
- enum :: (Text -> Maybe a) -> Value a
- custom :: (Bool -> ByteString -> Either Text a) -> Value a
- data Array a
- dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
- element :: Value a -> Array a
- nullableElement :: Value a -> Array (Maybe a)
- data Composite a
- field :: Value a -> Composite a
- nullableField :: Value a -> Composite (Maybe a)
Result
Decoder of a query result.
Functor Result Source # | |
Default (Result Int64) Source # | Maps to |
Default (Row a) => Default (Result [a]) Source # | Maps to |
Default (Row a) => Default (Result (Maybe a)) Source # | Maps to |
Default (Result ()) Source # | Maps to |
Default (Row a) => Default (Result (Identity a)) Source # | Maps to |
Default (Row a) => Default (Result (Vector a)) Source # | Maps to |
Decode no value from the result.
Useful for statements like INSERT
or CREATE
.
rowsAffected :: Result Int64 Source #
Get the amount of rows affected by such statements as
UPDATE
or DELETE
.
singleRow :: Row a -> Result a Source #
Exactly one row.
Will raise the UnexpectedAmountOfRows
error if it's any other.
Specialized multi-row results
rowVector :: Row a -> Result (Vector a) Source #
Zero or more rows packed into the vector.
It's recommended to prefer this function to rowList
,
since it performs notably better.
Multi-row traversers
Row
Decoder of an individual row, which gets composed of column value decoders.
E.g.:
x :: Row (Maybe Int64, Text, TimeOfDay) x = (,,) <$> nullableColumn int8 <*> column text <*> column time
column :: Value a -> Row a Source #
Lift an individual non-nullable value decoder to a composable row decoder.
nullableColumn :: Value a -> Row (Maybe a) Source #
Lift an individual nullable value decoder to a composable row decoder.
Value
Decoder of an individual value.
Functor Value Source # | |
Default (Value Bool) Source # | Maps to |
Default (Value Char) Source # | Maps to |
Default (Value Double) Source # | Maps to |
Default (Value Float) Source # | Maps to |
Default (Value Int16) Source # | Maps to |
Default (Value Int32) Source # | Maps to |
Default (Value Int64) Source # | Maps to |
Default (Value (TimeOfDay, TimeZone)) Source # | Maps to |
Default (Value ByteString) Source # | Maps to |
Default (Value Scientific) Source # | Maps to |
Default (Value Text) Source # | Maps to |
Default (Value UTCTime) Source # | Maps to |
Default (Value Value) Source # | Maps to |
Default (Value UUID) Source # | Maps to |
Default (Value Day) Source # | Maps to |
Default (Value DiffTime) Source # | Maps to |
Default (Value TimeOfDay) Source # | Maps to |
Default (Value LocalTime) Source # | Maps to |
numeric :: Value Scientific Source #
Decoder of the NUMERIC
values.
bytea :: Value ByteString Source #
Decoder of the BYTEA
values.
timestamptz :: Value UTCTime Source #
Decoder of the TIMESTAMPTZ
values.
NOTICE
Postgres does not store the timezone information of TIMESTAMPTZ
.
Instead it stores a UTC value and performs silent conversions
to the currently set timezone, when dealt with in the text format.
However this library bypasses the silent conversions
and communicates with Postgres using the UTC values directly.
timetz :: Value (TimeOfDay, TimeZone) Source #
Decoder of the TIMETZ
values.
Unlike in case of TIMESTAMPTZ
,
Postgres does store the timezone information for TIMETZ
.
However the Haskell's "time" library does not contain any composite type,
that fits the task, so we use a pair of TimeOfDay
and TimeZone
to represent a value on the Haskell's side.
jsonBytes :: (ByteString -> Either Text a) -> Value a Source #
Decoder of the JSON
values into a raw JSON ByteString
.
jsonbBytes :: (ByteString -> Either Text a) -> Value a Source #
Decoder of the JSONB
values into a raw JSON ByteString
.
hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a Source #
A generic decoder of HSTORE
values.
Here's how you can use it to construct a specific value:
x :: Value [(Text, Maybe Text)]
x =
hstore replicateM
enum :: (Text -> Maybe a) -> Value a Source #
Given a partial mapping from text to value, produces a decoder of that value.
custom :: (Bool -> ByteString -> Either Text a) -> Value a Source #
Lifts a custom value decoder function to a Value
decoder.
Array
A generic array decoder.
Here's how you can use it to produce a specific array value decoder:
x :: Value [[Text]] x = array (dimensionreplicateM
(dimensionreplicateM
(element text)))
dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b Source #
A function for parsing a dimension of an array. Provides support for multi-dimensional arrays.
Accepts:
- An implementation of the
replicateM
function (Control.Monad.
,replicateM
Data.Vector.
), which determines the output value.replicateM
- A decoder of its components, which can be either another
dimension
,element
ornullableElement
.
Composite
Composable decoder of composite values (rows, records).