Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- valueParser :: Value a -> ByteString -> Either Text a
- type Value = BinaryParser
- int :: (Integral a, Bits a) => Value a
- float4 :: Value Float
- float8 :: Value Double
- bool :: Value Bool
- bytea_strict :: Value ByteString
- bytea_lazy :: Value LazyByteString
- text_strict :: Value Text
- text_lazy :: Value LazyText
- char :: Value Char
- fn :: (ByteString -> Either Text a) -> Value a
- numeric :: Value Scientific
- uuid :: Value UUID
- inet :: Value (NetAddr IP)
- json_ast :: Value Value
- json_bytes :: (ByteString -> Either Text a) -> Value a
- jsonb_ast :: Value Value
- jsonb_bytes :: (ByteString -> Either Text a) -> Value a
- date :: Value Day
- time_int :: Value TimeOfDay
- time_float :: Value TimeOfDay
- timetz_int :: Value (TimeOfDay, TimeZone)
- timetz_float :: Value (TimeOfDay, TimeZone)
- timestamp_int :: Value LocalTime
- timestamp_float :: Value LocalTime
- timestamptz_int :: Value UTCTime
- timestamptz_float :: Value UTCTime
- interval_int :: Value DiffTime
- interval_float :: Value DiffTime
- data Array a
- array :: Array a -> Value a
- valueArray :: Value a -> Array a
- nullableValueArray :: Value a -> Array (Maybe a)
- dimensionArray :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
- data Composite a
- composite :: Composite a -> Value a
- valueComposite :: Value a -> Composite a
- nullableValueComposite :: Value a -> Composite (Maybe a)
- hstore :: (forall m. Monad m => Int -> m (k, Maybe v) -> m r) -> Value k -> Value v -> Value r
- enum :: (Text -> Maybe a) -> Value a
- refine :: (a -> Either Text b) -> Value a -> Value b
Documentation
valueParser :: Value a -> ByteString -> Either Text a Source #
type Value = BinaryParser Source #
Primitive
bytea_strict :: Value ByteString Source #
BYTEA or any other type in its undecoded form.
bytea_lazy :: Value LazyByteString Source #
BYTEA or any other type in its undecoded form.
Textual
text_strict :: Value Text Source #
Any of the variable-length character types: BPCHAR, VARCHAR, NAME and TEXT.
text_lazy :: Value LazyText Source #
Any of the variable-length character types: BPCHAR, VARCHAR, NAME and TEXT.
Misc
json_bytes :: (ByteString -> Either Text a) -> Value a Source #
Given a function, which parses a plain UTF-8 JSON string encoded as a byte-array, produces a decoder.
jsonb_bytes :: (ByteString -> Either Text a) -> Value a Source #
Given a function, which parses a plain UTF-8 JSON string encoded as a byte-array, produces a decoder.
For those wondering, yes, JSONB is encoded as plain JSON string in the binary format of Postgres. Sad, but true.
Time
time_int :: Value TimeOfDay Source #
TIME
values decoding for servers, which have integer_datetimes
enabled.
time_float :: Value TimeOfDay Source #
TIME
values decoding for servers, which don't have integer_datetimes
enabled.
timetz_int :: Value (TimeOfDay, TimeZone) Source #
TIMETZ
values decoding for servers, which have integer_datetimes
enabled.
timetz_float :: Value (TimeOfDay, TimeZone) Source #
TIMETZ
values decoding for servers, which don't have integer_datetimes
enabled.
timestamp_int :: Value LocalTime Source #
TIMESTAMP
values decoding for servers, which have integer_datetimes
enabled.
timestamp_float :: Value LocalTime Source #
TIMESTAMP
values decoding for servers, which don't have integer_datetimes
enabled.
timestamptz_int :: Value UTCTime Source #
TIMESTAMP
values decoding for servers, which have integer_datetimes
enabled.
timestamptz_float :: Value UTCTime Source #
TIMESTAMP
values decoding for servers, which don't have integer_datetimes
enabled.
interval_int :: Value DiffTime Source #
INTERVAL
values decoding for servers, which don't have integer_datetimes
enabled.
interval_float :: Value DiffTime Source #
INTERVAL
values decoding for servers, which have integer_datetimes
enabled.
Exotic
Array
An efficient generic array decoder, which constructs the result value in place while parsing.
Here's how you can use it to produce a specific array value decoder:
x :: Value [ [ Text ] ] x = array (dimensionArray replicateM (fmap catMaybes (dimensionArray replicateM (nullableValueArray text))))
valueArray :: Value a -> Array a Source #
dimensionArray :: (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
dimensionArray
ornullableValueArray
.
Composite
HStore
hstore :: (forall m. Monad m => Int -> m (k, Maybe v) -> m r) -> Value k -> Value v -> Value r Source #
A function for generic in place parsing of an HStore value.
Accepts:
- An implementation of the
replicateM
function (Control.Monad.
,replicateM
Data.Vector.
), which determines how to produce the final datastructure from the rows.replicateM
- A decoder for keys.
- A decoder for values.
Here's how you can use it to produce a parser to list:
hstoreAsList :: Value [ ( Text , Maybe Text ) ] hstoreAsList = hstore replicateM text text