| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
PostgreSQL.Result.Row
Contents
Description
Things in this module are used for processing Postgres query result rows.
Synopsis
- data Row a
- runRow :: (Monad m, Applicative row) => Row a -> (forall x. ColumnRequest x -> m (row x)) -> m (row a)
- runRowPq :: (MonadError ProcessorErrors m, MonadIO m) => Result -> Row a -> m (RowNum -> m a)
- data ColumnRequest a = ColumnReqest {}
- data ColumnPosition
- column :: AutoColumn a => Row a
- columnWith :: Column a -> Row a
- fixedColumn :: AutoColumn a => ColumnNum -> Row a
- fixedColumnWith :: ColumnNum -> Column a -> Row a
- namedColumn :: AutoColumn a => ByteString -> Row a
- namedColumnWith :: ByteString -> Column a -> Row a
- class AutoRow a where
- genericRow :: (Generic a, AutoRow (Rep a Void)) => Row a
- class AutoColumnDelegate a
- newtype Fixed (index :: Nat) a = Fixed {- fromFixed :: a
 
- newtype Named (name :: Symbol) a = Named {- fromNamed :: a
 
Documentation
Result row parser
Since: 0.0.0
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
| Functor ColumnRequest Source # | |
| Defined in PostgreSQL.Result.Row Methods fmap :: (a -> b) -> ColumnRequest a -> ColumnRequest b # (<$) :: a -> ColumnRequest b -> ColumnRequest a # | |
data ColumnPosition Source #
Position of a column
Since: 0.0.0
Constructors
| FixedColumn ColumnNum | Column is at a fixed index. Since: 0.0.0 | 
| NamedColumn ByteString | Column has a fixed name. Since: 0.0.0 | 
Instances
| Eq ColumnPosition Source # | |
| Defined in PostgreSQL.Result.Row Methods (==) :: ColumnPosition -> ColumnPosition -> Bool # (/=) :: ColumnPosition -> ColumnPosition -> Bool # | |
| Ord ColumnPosition Source # | |
| Defined in PostgreSQL.Result.Row Methods compare :: ColumnPosition -> ColumnPosition -> Ordering # (<) :: ColumnPosition -> ColumnPosition -> Bool # (<=) :: ColumnPosition -> ColumnPosition -> Bool # (>) :: ColumnPosition -> ColumnPosition -> Bool # (>=) :: ColumnPosition -> ColumnPosition -> Bool # max :: ColumnPosition -> ColumnPosition -> ColumnPosition # min :: ColumnPosition -> ColumnPosition -> ColumnPosition # | |
| Read ColumnPosition Source # | |
| Defined in PostgreSQL.Result.Row Methods readsPrec :: Int -> ReadS ColumnPosition # readList :: ReadS [ColumnPosition] # | |
| Show ColumnPosition Source # | |
| Defined in PostgreSQL.Result.Row Methods showsPrec :: Int -> ColumnPosition -> ShowS # show :: ColumnPosition -> String # showList :: [ColumnPosition] -> ShowS # | |
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
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
Instances
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 = genericRowSince: 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
| AutoColumn a => AutoColumnDelegate a Source # | Passthrough to  Since: 0.0.0 | 
| Defined in PostgreSQL.Result.Row Methods autoColumnDelegate :: Row a | |
| (KnownSymbol name, AutoColumn a) => AutoColumnDelegate (Named name a) Source # | Uses  Since: 0.0.0 | 
| Defined in PostgreSQL.Result.Row Methods autoColumnDelegate :: Row (Named name a) | |
| (KnownNat index, AutoColumn a) => AutoColumnDelegate (Fixed index a) Source # | Uses  Since: 0.0.0 | 
| 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
Instances
| (KnownNat index, AutoColumn a) => AutoColumnDelegate (Fixed index a) Source # | Uses  Since: 0.0.0 | 
| 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
Instances
| (KnownSymbol name, AutoColumn a) => AutoColumnDelegate (Named name a) Source # | Uses  Since: 0.0.0 | 
| Defined in PostgreSQL.Result.Row Methods autoColumnDelegate :: Row (Named name a) | |