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

Safe HaskellNone
LanguageHaskell2010

PostgreSQL.Binary.Decoding

Contents

Synopsis

Documentation

Primitive

int :: (Integral a, Bits a) => Value a Source #

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.

char :: Value Char Source #

A UTF-8-decoded char.

Misc

fn :: (ByteString -> Either Text a) -> Value a Source #

Lifts a custom decoder implementation.

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

date :: Value Day Source #

DATE values decoding.

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

data Array 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 :: Value [ [ Text ] ]
x =
  array (dimensionArray replicateM (fmap catMaybes (dimensionArray replicateM (nullableValueArray text))))
Instances
Functor Array Source # 
Instance details

Defined in PostgreSQL.Binary.Decoding

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

array :: Array a -> Value a Source #

Unlift an Array to a value Value.

valueArray :: Value a -> Array a Source #

Lift a value Value into Array for parsing of non-nullable leaf values.

nullableValueArray :: Value a -> Array (Maybe a) Source #

Lift a value Value into Array for parsing of nullable leaf values.

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:

Composite

data Composite a Source #

Instances
Monad Composite Source # 
Instance details

Defined in PostgreSQL.Binary.Decoding

Methods

(>>=) :: Composite a -> (a -> Composite b) -> Composite b #

(>>) :: Composite a -> Composite b -> Composite b #

return :: a -> Composite a #

fail :: String -> Composite a #

Functor Composite Source # 
Instance details

Defined in PostgreSQL.Binary.Decoding

Methods

fmap :: (a -> b) -> Composite a -> Composite b #

(<$) :: a -> Composite b -> Composite a #

Applicative Composite Source # 
Instance details

Defined in PostgreSQL.Binary.Decoding

Methods

pure :: a -> Composite a #

(<*>) :: Composite (a -> b) -> Composite a -> Composite b #

liftA2 :: (a -> b -> c) -> Composite a -> Composite b -> Composite c #

(*>) :: Composite a -> Composite b -> Composite b #

(<*) :: Composite a -> Composite b -> Composite a #

composite :: Composite a -> Value a Source #

Unlift a Composite to a value Value.

valueComposite :: Value a -> Composite a Source #

Lift a non-nullable value Value into 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.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 :: Value [ ( Text , Maybe Text ) ]
hstoreAsList =
  hstore replicateM text text

enum :: (Text -> Maybe a) -> Value a Source #

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

refine :: (a -> Either Text b) -> Value a -> Value b Source #

Given additional constraints when using an existing value decoder, produces a decoder of that value.