postgresql-binary-0.7.5.1: Encoders and decoders for the PostgreSQL's binary format

Safe HaskellNone
LanguageHaskell2010

PostgreSQL.Binary.Decoder

Contents

Synopsis

Documentation

run :: BinaryParser a -> ByteString -> Either Text a

Apply a parser to bytes.

Primitive

int :: (Integral a, Bits a) => Decoder a Source

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.

char :: Decoder Char Source

A UTF-8-decoded char.

Misc

Time

date :: Decoder Day Source

DATE values decoding.

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))))

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:

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

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.replicateM), which determines how to produce the final datastructure from the rows.
  • 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

enum :: (Text -> Maybe a) -> Decoder a Source

Given a partial mapping from text to value, produces a decoder of that value.