pg-store-0.4.0: Simple storage interface to PostgreSQL

Copyright(c) Ole Krüger 2016
LicenseBSD3
MaintainerOle Krüger <ole@vprsm.de>
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Store.RowParser

Contents

Description

 

Synopsis

Row parser

data RowParser w a Source #

Consumes w columns of a result set row in order to produce an instance of a.

Instances

Functor (RowParser w) Source # 

Methods

fmap :: (a -> b) -> RowParser w a -> RowParser w b #

(<$) :: a -> RowParser w b -> RowParser w a #

processResultWith :: forall a n. KnownNat n => Result -> RowParser n a -> ExceptT RowError IO [a] Source #

Process the each row of the Result with the given RowParser.

Means of composition

(>>=$) :: forall a v b w. KnownNat v => RowParser v a -> (a -> RowParser w b) -> RowParser (v + w) b infixl 1 Source #

Transform the result of another RowParser. Similar to monadic bind. Also keeps track of how many columns are needed in total.

(>>$) :: forall a v b w. KnownNat v => RowParser v a -> RowParser w b -> RowParser (v + w) b infixl 1 Source #

Chain two RowParsers, but discard the result of the first.

(<*>$) :: forall a v b w. KnownNat v => RowParser v (a -> b) -> RowParser w a -> RowParser (v + w) b infixl 4 Source #

Just like the '(*)' operator.

finish :: a -> RowParser 0 a Source #

Terminate the parsing tree by returning the final result.

cancel :: RowErrorDetail -> RowParser 0 a Source #

Terminate the parsing tree with an error.

skipColumns :: RowParser n () Source #

Skip a number of columns.

nonNullCheck :: Int -> RowParser 0 Bool Source #

Check if the following n columns are not NULL.

Default parsers

processContent :: (Oid -> Maybe ByteString -> Maybe a) -> RowParser 1 a Source #

Process the contents of a column.

retrieveColumn :: RowParser 1 (Oid, Maybe ByteString) Source #

Retrieve a column's type and content.

retrieveContent :: RowParser 1 ByteString Source #

Retrieve a column's content.