psql-0.0.0: PostgreSQL client
Safe HaskellNone
LanguageHaskell2010

PostgreSQL.Result.Row

Description

Things in this module are used for processing Postgres query result rows.

Synopsis

Documentation

data Row a Source #

Result row parser

Since: 0.0.0

Instances

Instances details
Functor Row Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

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

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

Applicative Row Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

pure :: a -> Row a #

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

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

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

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

Apply Row Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

(<.>) :: Row (a -> b) -> Row a -> Row b

(.>) :: Row a -> Row b -> Row b

(<.) :: Row a -> Row b -> Row a

liftF2 :: (a -> b -> c) -> Row a -> Row b -> Row c

runRow :: (Monad m, Applicative row) => Row a -> (forall x. ColumnRequest x -> m (row x)) -> m (row a) Source #

Translate a Row expression. Validate things in m and parse each row in row.

Since: 0.0.0

runRowPq :: (MonadError ProcessorErrors m, MonadIO m) => Result -> Row a -> m (RowNum -> m a) Source #

Generate a row runner for libpq's Result.

Since: 0.0.0

data ColumnRequest a Source #

Request a column

Since: 0.0.0

Constructors

ColumnReqest

Since: 0.0.0

Fields

Instances

Instances details
Functor ColumnRequest Source # 
Instance details

Defined in PostgreSQL.Result.Row

Methods

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

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

Combinators

column :: AutoColumn a => Row a Source #

Floating column using the default Column for a

The position of this column is depenend on other floating columns left of it.

For example:

foo = baz <$> column <*> column <*> column
--            ^ A        ^ B        ^ C

Here, A would be at index 0, B at 1 and C at 2. Other non-floating columns do not impact the column indices.

Since: 0.0.0

columnWith :: Column a -> Row a Source #

Same as column but lets you specify the Column.

Since: 0.0.0

fixedColumn :: AutoColumn a => ColumnNum -> Row a Source #

Fixed-position column using the default Column for a

Since: 0.0.0

fixedColumnWith :: ColumnNum -> Column a -> Row a Source #

Same as fixedColumn but lets you specify the Column.

Since: 0.0.0

namedColumn :: AutoColumn a => ByteString -> Row a Source #

Named column using the default Column for a

Since: 0.0.0

namedColumnWith :: ByteString -> Column a -> Row a Source #

Same as namedColumn but lets you specify the Column.

Since: 0.0.0

Class

class AutoRow a where Source #

Default row parser for a type

Since: 0.0.0

Minimal complete definition

Nothing

Methods

autoRow :: Row a Source #

Default row parser for a

You may omit a definition for autoRow if a implements Generic.

Since: 0.0.0

default autoRow :: (Generic a, AutoRow (Rep a Void)) => Row a Source #

Instances

Instances details
AutoColumnDelegate a => AutoRow (Identity a) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (Identity a) Source #

(AutoColumnDelegate a, AutoColumnDelegate b) => AutoRow (a, b) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b) Source #

(AutoColumnDelegate a, AutoColumnDelegate b, AutoColumnDelegate c) => AutoRow (a, b, c) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b, c) Source #

AutoColumnDelegate a => AutoRow (K1 tag a x) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (K1 tag a x) Source #

(AutoRow (lhs x), AutoRow (rhs x)) => AutoRow ((lhs :*: rhs) x) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row ((lhs :*: rhs) x) Source #

(AutoColumnDelegate a, AutoColumnDelegate b, AutoColumnDelegate c, AutoColumnDelegate d) => AutoRow (a, b, c, d) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b, c, d) Source #

AutoRow (f x) => AutoRow (M1 tag meta f x) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (M1 tag meta f x) Source #

(AutoColumnDelegate a, AutoColumnDelegate b, AutoColumnDelegate c, AutoColumnDelegate d, AutoColumnDelegate e) => AutoRow (a, b, c, d, e) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b, c, d, e) Source #

(AutoColumnDelegate a, AutoColumnDelegate b, AutoColumnDelegate c, AutoColumnDelegate d, AutoColumnDelegate e, AutoColumnDelegate f) => AutoRow (a, b, c, d, e, f) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b, c, d, e, f) Source #

(AutoColumnDelegate a, AutoColumnDelegate b, AutoColumnDelegate c, AutoColumnDelegate d, AutoColumnDelegate e, AutoColumnDelegate f, AutoColumnDelegate g) => AutoRow (a, b, c, d, e, f, g) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoRow :: Row (a, b, c, d, e, f, g) Source #

genericRow :: (Generic a, AutoRow (Rep a Void)) => Row a Source #

Generic row parser

You can use this with your Generic-implementing data types.

data Foo = Foo
  { bar :: Integer
  , baz :: Text
  }
  deriving Generic

fooRow :: Row Foo
fooRow = genericRow

Since: 0.0.0

class AutoColumnDelegate a Source #

This class is used to intercept instance heads like Fixed and Named that have special additional meaning. For most cases it will delegate to AutoColumn.

Use this class instead of AutoColumn when implementing AutoRow instances.

Since: 0.0.0

Minimal complete definition

autoColumnDelegate

Instances

Instances details
AutoColumn a => AutoColumnDelegate a Source #

Passthrough to AutoColumn

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

(KnownSymbol name, AutoColumn a) => AutoColumnDelegate (Named name a) Source #

Uses namedColumn with name to construct the Row

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoColumnDelegate :: Row (Named name a)

(KnownNat index, AutoColumn a) => AutoColumnDelegate (Fixed index a) Source #

Uses fixedColumn with index to construct the Row

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoColumnDelegate :: Row (Fixed index a)

Helpers

newtype Fixed (index :: Nat) a Source #

Value for a column at a fixed location

Since: 0.0.0

Constructors

Fixed 

Fields

Instances

Instances details
(KnownNat index, AutoColumn a) => AutoColumnDelegate (Fixed index a) Source #

Uses fixedColumn with index to construct the Row

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoColumnDelegate :: Row (Fixed index a)

newtype Named (name :: Symbol) a Source #

Value for a named column

Since: 0.0.0

Constructors

Named 

Fields

Instances

Instances details
(KnownSymbol name, AutoColumn a) => AutoColumnDelegate (Named name a) Source #

Uses namedColumn with name to construct the Row

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Row

Methods

autoColumnDelegate :: Row (Named name a)