Safe Haskell | None |
---|---|
Language | Haskell2010 |
A DSL for declaration of result decoders.
Synopsis
- data Result a
- noResult :: 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 :: NullableOrNot Value a -> Row a
- data NullableOrNot (decoder :: Type -> Type) a
- nonNullable :: decoder a -> NullableOrNot decoder a
- nullable :: decoder a -> NullableOrNot decoder (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 IPRange
- 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
- listArray :: NullableOrNot Value element -> Value [element]
- vectorArray :: Vector vector element => NullableOrNot Value element -> Value (vector element)
- composite :: Composite a -> Value a
- hstore :: (forall (m :: Type -> Type). 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
- refine :: (a -> Either Text b) -> Value a -> Value b
- data Array a
- dimension :: (forall (m :: Type -> Type). Monad m => Int -> m a -> m b) -> Array a -> Array b
- element :: NullableOrNot Value a -> Array a
- data Composite a
- field :: NullableOrNot Value a -> Composite a
Result
Decoder of a query result.
noResult :: Result () Source #
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 = (,,)<$>
(column
.nullable
)int8
<*>
(column
.nonNullable
)text
<*>
(column
.nonNullable
)time
column :: NullableOrNot Value a -> Row a Source #
Lift an individual value decoder to a composable row decoder.
Nullability
data NullableOrNot (decoder :: Type -> Type) a Source #
Extensional specification of nullability over a generic decoder.
nonNullable :: decoder a -> NullableOrNot decoder a Source #
Specify that a decoder produces a non-nullable value.
nullable :: decoder a -> NullableOrNot decoder (Maybe a) Source #
Specify that a decoder produces a nullable value.
Value
Decoder of a value.
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.
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
.
listArray :: NullableOrNot Value element -> Value [element] Source #
Lift a value decoder of element into a unidimensional array decoder producing a list.
This function is merely a shortcut to the following expression:
(array
.dimension
Control.Monad.replicateM
.element
)
Please notice that in case of multidimensional arrays nesting listArray
decoder
won't work. You have to explicitly construct the array decoder using array
.
vectorArray :: Vector vector element => NullableOrNot Value element -> Value (vector element) Source #
Lift a value decoder of element into a unidimensional array decoder producing a generic vector.
This function is merely a shortcut to the following expression:
(array
.dimension
Data.Vector.Generic.replicateM
.element
)
Please notice that in case of multidimensional arrays nesting vectorArray
decoder
won't work. You have to explicitly construct the array decoder using array
.
hstore :: (forall (m :: Type -> Type). 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 #
Lift a custom value decoder function to a Value
decoder.
refine :: (a -> Either Text b) -> Value a -> Value b Source #
Refine a value decoder, lifting the possible error to the session level.
Array
A generic array decoder.
Here's how you can use it to produce a specific array value decoder:
x ::Value
[[Text]] x =array
(dimension
replicateM
(dimension
replicateM
(element
(nonNullable
text
))))
dimension :: (forall (m :: Type -> Type). 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
orelement
.