Safe Haskell | None |
---|---|
Language | Haskell2010 |
PostgreSQL.Binary.Decoder
- type Decoder = BinaryParser
- run :: BinaryParser a -> ByteString -> Either Text a
- int :: (Integral a, Bits a) => Decoder a
- float4 :: Decoder Float
- float8 :: Decoder Double
- bool :: Decoder Bool
- bytea_strict :: Decoder ByteString
- bytea_lazy :: Decoder LazyByteString
- text_strict :: Decoder Text
- text_lazy :: Decoder LazyText
- char :: Decoder Char
- numeric :: Decoder Scientific
- uuid :: Decoder UUID
- json :: Decoder Value
- date :: Decoder Day
- time_int :: Decoder TimeOfDay
- time_float :: Decoder TimeOfDay
- timetz_int :: Decoder (TimeOfDay, TimeZone)
- timetz_float :: Decoder (TimeOfDay, TimeZone)
- timestamp_int :: Decoder LocalTime
- timestamp_float :: Decoder LocalTime
- timestamptz_int :: Decoder UTCTime
- timestamptz_float :: Decoder UTCTime
- interval_int :: Decoder DiffTime
- interval_float :: Decoder DiffTime
- data ArrayDecoder a
- array :: ArrayDecoder a -> Decoder a
- arrayDimension :: (forall m. Monad m => Int -> m a -> m b) -> ArrayDecoder a -> ArrayDecoder b
- arrayValue :: Decoder a -> ArrayDecoder (Maybe a)
- arrayNonNullValue :: Decoder a -> ArrayDecoder a
- data CompositeDecoder a
- composite :: CompositeDecoder a -> Decoder a
- compositeValue :: Decoder a -> CompositeDecoder (Maybe a)
- compositeNonNullValue :: Decoder a -> CompositeDecoder a
- hstore :: (forall m. Monad m => Int -> m (k, Maybe v) -> m r) -> Decoder k -> Decoder v -> Decoder r
- enum :: (Text -> Maybe a) -> Decoder a
Documentation
type Decoder = BinaryParser Source
run :: BinaryParser a -> ByteString -> Either Text a
Apply a parser to bytes.
Primitive
bytea_strict :: Decoder ByteString Source
BYTEA or any other type in its undecoded form.
bytea_lazy :: Decoder LazyByteString Source
BYTEA or any other type in its undecoded form.
Textual
text_strict :: Decoder Text Source
Any of the variable-length character types: BPCHAR, VARCHAR, NAME and TEXT.
text_lazy :: Decoder LazyText Source
Any of the variable-length character types: BPCHAR, VARCHAR, NAME and TEXT.
Misc
Time
time_int :: Decoder TimeOfDay Source
TIME
values decoding for servers, which have integer_datetimes
enabled.
time_float :: Decoder TimeOfDay Source
TIME
values decoding for servers, which don't have integer_datetimes
enabled.
timetz_int :: Decoder (TimeOfDay, TimeZone) Source
TIMETZ
values decoding for servers, which have integer_datetimes
enabled.
timetz_float :: Decoder (TimeOfDay, TimeZone) Source
TIMETZ
values decoding for servers, which don't have integer_datetimes
enabled.
timestamp_int :: Decoder LocalTime Source
TIMESTAMP
values decoding for servers, which have integer_datetimes
enabled.
timestamp_float :: Decoder LocalTime Source
TIMESTAMP
values decoding for servers, which don't have integer_datetimes
enabled.
timestamptz_int :: Decoder UTCTime Source
TIMESTAMP
values decoding for servers, which have integer_datetimes
enabled.
timestamptz_float :: Decoder UTCTime Source
TIMESTAMP
values decoding for servers, which don't have integer_datetimes
enabled.
interval_int :: Decoder DiffTime Source
INTERVAL
values decoding for servers, which don't have integer_datetimes
enabled.
interval_float :: Decoder DiffTime Source
INTERVAL
values decoding for servers, which have integer_datetimes
enabled.
Exotic
Array
data ArrayDecoder a Source
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 :: Decoder [ [ Text ] ] x = array (arrayDimension replicateM (fmap catMaybes (arrayDimension replicateM (arrayValue text))))
Instances
array :: ArrayDecoder a -> Decoder a Source
Unlift an ArrayDecoder
to a value Decoder
.
arrayDimension :: (forall m. Monad m => Int -> m a -> m b) -> ArrayDecoder a -> ArrayDecoder 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
arrayDimension
orarrayValue
.
arrayValue :: Decoder a -> ArrayDecoder (Maybe a) Source
Lift a value Decoder
into ArrayDecoder
for parsing of nullable leaf values.
arrayNonNullValue :: Decoder a -> ArrayDecoder a Source
Lift a value Decoder
into ArrayDecoder
for parsing of non-nullable leaf values.
Composite
data CompositeDecoder a Source
composite :: CompositeDecoder a -> Decoder a Source
Unlift a CompositeDecoder
to a value Decoder
.
compositeValue :: Decoder a -> CompositeDecoder (Maybe a) Source
Lift a value Decoder
into CompositeDecoder
.
compositeNonNullValue :: Decoder a -> CompositeDecoder a Source
Lift a non-nullable value Decoder
into CompositeDecoder
.
HStore
hstore :: (forall m. Monad m => Int -> m (k, Maybe v) -> m r) -> Decoder k -> Decoder v -> Decoder 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 :: Decoder [ ( Text , Maybe Text ) ] hstoreAsList = hstore replicateM text text