psql-0.0.0: PostgreSQL client
Safe HaskellNone
LanguageHaskell2010

PostgreSQL

Description

PostgreSQL client

Have a look at the individual sub-sections to find out more about the respective concepts.

Synopsis

Templates and statements

Writing a statement usually involves writing it as a Template and then rendering it as a Statement. The latter can optionally be prepared to become a PreparedStatement.

Templates and statements can take an input. The type of that input is determined by the type parameter that Template, Statement and 'Statement.PreparedStatement expose.

Templates

Templates can be constructed using the tpl quasi-quoter or manually using the provided combinators.

data Template a Source #

SQL statement template

Since: 0.0.0

Instances

Instances details
Contravariant Template Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

contramap :: (a -> b) -> Template b -> Template a #

(>$) :: b -> Template b -> Template a #

(HasField n r a, Param a) => IsLabel n (Template r) Source #

OverloadedLabels helper for param

#myParam === param (getField @"myParam")

Use this with a database:

data MyFoo = MyFoo { bar :: Int, baz :: String }

myStatementTpl :: Template MyFoo
myStatementTpl = "SELECT * FROM my_foo WHERE bar = " <> #bar <> " AND baz = " <> #baz

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

fromLabel :: Template r #

IsString (Template a) Source #

OverloadedStrings helper for code

"my code" === code "my code"

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

fromString :: String -> Template a #

Semigroup (Template a) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

(<>) :: Template a -> Template a -> Template a #

sconcat :: NonEmpty (Template a) -> Template a #

stimes :: Integral b => b -> Template a -> Template a #

Monoid (Template a) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

mempty :: Template a #

mappend :: Template a -> Template a -> Template a #

mconcat :: [Template a] -> Template a #

renderTemplate :: Template a -> Statement a Source #

Render the SQL statement.

Since: 0.0.0

Quasi-quotation

tpl :: QuasiQuoter Source #

Produces a Template expression.

Supports the same features as stmt.

Since: 0.0.0

Combinators

Template implements Semigroup and Monoid. These can be used to compose the following combinators.

It also supports IsString which helps to create templates from string literals.

You may use overloaded labels to refer to parameters.

#my_param === param my_param

my_param shall be a record field of data type.

code :: Text -> Template a Source #

Create a code-only statement.

Since: 0.0.0

identifier :: Text -> Template a Source #

Create a code segment that mentions the given identifier (e.g. table or column name).

Since: 0.0.0

string :: Text -> Template a Source #

Encase the given string literal in single quotes. Single quotes in the literal are automatically escaped.

Since: 0.0.0

param :: forall b a. Param b => (a -> b) -> Template a Source #

Reference a parameter.

Since: 0.0.0

paramWith :: Info (a -> Value) -> Template a Source #

Reference a parameter.

Since: 0.0.0

constant :: forall b a. Param b => b -> Template a Source #

Constant part of a query.

Since: 0.0.0

Statements

Statements are created using the stmt quasi-quoter or by rendering a Template via renderTemplate.

data Statement a Source #

Rendered SQL statement

Since: 0.0.0

Instances

Instances details
Contravariant Statement Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Methods

contramap :: (a -> b) -> Statement b -> Statement a #

(>$) :: b -> Statement b -> Statement a #

Executable Statement Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Query.Class

Methods

execute :: Query query => Statement param -> param -> query (NativeResult query) Source #

stmt :: QuasiQuoter Source #

Produces a Statement expression.

[stmt| SELECT $param * 2 |]

Use $$ to render a single $.

Parameters

Use $param or ${param} to reference a query parameter.

[stmt| ${x} |] is equivalent to param x.

Substitutions

Use $(substr) to embed another Template where substr :: Template a.

[stmt| $(x) |] is equivalent to x.

Examples

data MyParams = MyParams { foo :: Int, bar :: Text }

myStatement :: Statement MyParams
myStatement = [stmt| SELECT baz FROM my_table WHERE foo > ${foo} AND bar = ${bar} |]

Since: 0.0.0

Prepared statements

PreparedStatements can be obtained using withPreparedStatement.

This can be useful when executing a statement repeatedly and you want to save some time on parsing and type-checking the statement on the database server.

data PreparedStatement a Source #

Prepared statement

Since: 0.0.0

Instances

Instances details
Contravariant PreparedStatement Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Statement

Executable PreparedStatement Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Query.Class

Methods

execute :: Query query => PreparedStatement param -> param -> query (NativeResult query) Source #

Query execution

Queries are built using any type query that satisfies Query query. The combinators below are used to run or prepare statements.

In most cases you will use runQuery or runQueryThrow to then actually run the query.

ConnectionPoolT is a useful interpreter for the RunQuery effect.

Combinators

execute Source #

Arguments

:: (Executable statement, Query query) 
=> statement param

Statement

-> param

Statement input

-> query (NativeResult query) 

Execute a statement.

Since: 0.0.0

execute_ Source #

Arguments

:: (Executable statement, Query query) 
=> statement param

Statement

-> param

Statement input

-> query () 

Like execute but does not concern itself with the result handle.

Since: 0.0.0

query Source #

Arguments

:: (Executable statement, Query query, AutoRow row) 
=> statement param

Query statement

-> param

Query parameter

-> query (Vector row) 

Perform a parameterized query.

Since: 0.0.0

queryWith Source #

Arguments

:: (Executable statement, Query query) 
=> statement param

Query statement

-> param

Query parameter

-> Result row

Result row processor

-> query row 

Perform a parameterized query. This also lets you specify the result processor explicitly.

Since: 0.0.0

withPreparedStatement Source #

Arguments

:: Query query 
=> Statement a

Statement to prepare

-> (PreparedStatement a -> query r)

Scope within the prepared statement may be used

-> query r 

Prepare a statement. The prepared statement is only valid within the provided continuation.

Since: 0.0.0

Evaluation

class Monad query => Query query Source #

PostgreSQL query

Since: 0.0.0

Instances

Instances details
(MonadIO m, MonadMask m) => Query (QueryT m) Source # 
Instance details

Defined in PostgreSQL.Query

Associated Types

type NativeResult (QueryT m) Source #

class Query query => RunQuery query m | m -> query where Source #

PostgreSQL queries can be executed in m

Since: 0.0.0

Methods

runQuery :: query a -> m (Either Errors a) Source #

Run a query.

Since: 0.0.0

Instances

Instances details
(RunQuery query m, Monad m, MonadTrans t) => RunQuery query (t m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Class

Methods

runQuery :: query a -> t m (Either Errors a) Source #

(MonadMask m, MonadIO m) => RunQuery (QueryT m) (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

runQueryThrow :: (MonadThrow m, RunQuery query m) => query a -> m a Source #

Like runQuery but throws the first error instead.

Since: 0.0.0

Interpreters

data ConnectionPoolT m a Source #

Interpreter for RunQuery which dispatches queries to a pool of database connections

Since: 0.0.0

Instances

Instances details
MonadTrans ConnectionPoolT Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

lift :: Monad m => m a -> ConnectionPoolT m a #

MonadWriter w m => MonadWriter w (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

writer :: (a, w) -> ConnectionPoolT m a #

tell :: w -> ConnectionPoolT m () #

listen :: ConnectionPoolT m a -> ConnectionPoolT m (a, w) #

pass :: ConnectionPoolT m (a, w -> w) -> ConnectionPoolT m a #

MonadState s m => MonadState s (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

get :: ConnectionPoolT m s #

put :: s -> ConnectionPoolT m () #

state :: (s -> (a, s)) -> ConnectionPoolT m a #

MonadError e m => MonadError e (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Monad m => Monad (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Functor m => Functor (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

fmap :: (a -> b) -> ConnectionPoolT m a -> ConnectionPoolT m b #

(<$) :: a -> ConnectionPoolT m b -> ConnectionPoolT m a #

MonadFail m => MonadFail (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

fail :: String -> ConnectionPoolT m a #

Applicative m => Applicative (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

MonadIO m => MonadIO (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

liftIO :: IO a -> ConnectionPoolT m a #

MonadThrow m => MonadThrow (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

throwM :: Exception e => e -> ConnectionPoolT m a #

MonadCatch m => MonadCatch (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

catch :: Exception e => ConnectionPoolT m a -> (e -> ConnectionPoolT m a) -> ConnectionPoolT m a #

MonadMask m => MonadMask (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Methods

mask :: ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m b) -> ConnectionPoolT m b #

uninterruptibleMask :: ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m b) -> ConnectionPoolT m b #

generalBracket :: ConnectionPoolT m a -> (a -> ExitCase b -> ConnectionPoolT m c) -> (a -> ConnectionPoolT m b) -> ConnectionPoolT m (b, c) #

MonadConc m => MonadConc (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

Associated Types

type STM (ConnectionPoolT m) :: Type -> Type

type MVar (ConnectionPoolT m) :: Type -> Type

type IORef (ConnectionPoolT m) :: Type -> Type

type Ticket (ConnectionPoolT m) :: Type -> Type

type ThreadId (ConnectionPoolT m)

Methods

forkWithUnmask :: ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

forkWithUnmaskN :: String -> ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

forkOnWithUnmask :: Int -> ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

forkOnWithUnmaskN :: String -> Int -> ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

forkOSWithUnmask :: ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

forkOSWithUnmaskN :: String -> ((forall a. ConnectionPoolT m a -> ConnectionPoolT m a) -> ConnectionPoolT m ()) -> ConnectionPoolT m (ThreadId (ConnectionPoolT m))

supportsBoundThreads :: ConnectionPoolT m Bool

isCurrentThreadBound :: ConnectionPoolT m Bool

getNumCapabilities :: ConnectionPoolT m Int

setNumCapabilities :: Int -> ConnectionPoolT m ()

myThreadId :: ConnectionPoolT m (ThreadId (ConnectionPoolT m))

yield :: ConnectionPoolT m ()

threadDelay :: Int -> ConnectionPoolT m ()

newEmptyMVar :: ConnectionPoolT m (MVar (ConnectionPoolT m) a)

newEmptyMVarN :: String -> ConnectionPoolT m (MVar (ConnectionPoolT m) a)

putMVar :: MVar (ConnectionPoolT m) a -> a -> ConnectionPoolT m ()

tryPutMVar :: MVar (ConnectionPoolT m) a -> a -> ConnectionPoolT m Bool

readMVar :: MVar (ConnectionPoolT m) a -> ConnectionPoolT m a

tryReadMVar :: MVar (ConnectionPoolT m) a -> ConnectionPoolT m (Maybe a)

takeMVar :: MVar (ConnectionPoolT m) a -> ConnectionPoolT m a

tryTakeMVar :: MVar (ConnectionPoolT m) a -> ConnectionPoolT m (Maybe a)

newIORef :: a -> ConnectionPoolT m (IORef (ConnectionPoolT m) a)

newIORefN :: String -> a -> ConnectionPoolT m (IORef (ConnectionPoolT m) a)

readIORef :: IORef (ConnectionPoolT m) a -> ConnectionPoolT m a

atomicModifyIORef :: IORef (ConnectionPoolT m) a -> (a -> (a, b)) -> ConnectionPoolT m b

writeIORef :: IORef (ConnectionPoolT m) a -> a -> ConnectionPoolT m ()

atomicWriteIORef :: IORef (ConnectionPoolT m) a -> a -> ConnectionPoolT m ()

readForCAS :: IORef (ConnectionPoolT m) a -> ConnectionPoolT m (Ticket (ConnectionPoolT m) a)

peekTicket' :: Proxy (ConnectionPoolT m) -> Ticket (ConnectionPoolT m) a -> a

casIORef :: IORef (ConnectionPoolT m) a -> Ticket (ConnectionPoolT m) a -> a -> ConnectionPoolT m (Bool, Ticket (ConnectionPoolT m) a)

modifyIORefCAS :: IORef (ConnectionPoolT m) a -> (a -> (a, b)) -> ConnectionPoolT m b

modifyIORefCAS_ :: IORef (ConnectionPoolT m) a -> (a -> a) -> ConnectionPoolT m ()

atomically :: STM (ConnectionPoolT m) a -> ConnectionPoolT m a

newTVarConc :: a -> ConnectionPoolT m (TVar (STM (ConnectionPoolT m)) a)

readTVarConc :: TVar (STM (ConnectionPoolT m)) a -> ConnectionPoolT m a

throwTo :: Exception e => ThreadId (ConnectionPoolT m) -> e -> ConnectionPoolT m ()

getMaskingState :: ConnectionPoolT m MaskingState

unsafeUnmask :: ConnectionPoolT m a -> ConnectionPoolT m a

(MonadMask m, MonadIO m) => RunQuery (QueryT m) (ConnectionPoolT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.ConnectionPool

type IORef (ConnectionPoolT m) Source # 
Instance details

Defined in PostgreSQL.ConnectionPool

type IORef (ConnectionPoolT m) = IORef (PoolT Connection m)
type MVar (ConnectionPoolT m) Source # 
Instance details

Defined in PostgreSQL.ConnectionPool

type MVar (ConnectionPoolT m) = MVar (PoolT Connection m)
type STM (ConnectionPoolT m) Source # 
Instance details

Defined in PostgreSQL.ConnectionPool

type STM (ConnectionPoolT m) = STM (PoolT Connection m)
type ThreadId (ConnectionPoolT m) Source # 
Instance details

Defined in PostgreSQL.ConnectionPool

type ThreadId (ConnectionPoolT m) = ThreadId (PoolT Connection m)
type Ticket (ConnectionPoolT m) Source # 
Instance details

Defined in PostgreSQL.ConnectionPool

type Ticket (ConnectionPoolT m) = Ticket (PoolT Connection m)

runConnectionPoolT Source #

Arguments

:: (MonadIO m, MonadConc m) 
=> m Connection

Action to establish a new connection

-> Settings

Connection pool settings

-> ConnectionPoolT m a

Transformer to run

-> m a 

Run connection pool transformer.

Since: 0.0.0

defaultConnectionPoolSettings :: Settings Source #

Default settings for the connection pool

Since: 0.0.0

Result processing

Top level

data Result a Source #

Query result

Since: 0.0.0

Instances

Instances details
Functor Result Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result

Methods

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

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

ignored :: Result () Source #

Ignore the result set.

Since: 0.0.0

single :: Row a -> Result a Source #

Process exactly 1 row.

Since: 0.0.0

first :: Row a -> Result a Source #

Process only the first row. There may be more rows in the result set, but they won't be touched.

Since: 0.0.0

many :: Row a -> Result (Vector a) Source #

Process 0 or more rows.

Since: 0.0.0

affectedRows :: Result Integer Source #

Get the number of affected rows.

Since: 0.0.0

Row level

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

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

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)

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

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)

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)

Column level

data Column a Source #

Result column parser

Since: 0.0.0

Instances

Instances details
Functor Column Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Methods

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

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

Alt Column Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Methods

(<!>) :: Column a -> Column a -> Column a

some :: Applicative Column => Column a -> Column [a]

many :: Applicative Column => Column a -> Column [a]

class AutoColumn a where Source #

Default column parser for a type

Since: 0.0.0

Methods

autoColumn :: Column a Source #

Default column parser for a

Since: 0.0.0

Instances

Instances details
AutoColumn Double Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Float Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Int Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Integer Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Natural Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Word Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn () Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Methods

autoColumn :: Column () Source #

AutoColumn Text Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

AutoColumn RawValue Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Read a => AutoColumn (Readable a) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

(AutoColumn a, AutoColumn b) => AutoColumn (Either a b) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Methods

autoColumn :: Column (Either a b) Source #

newtype Readable a Source #

Provides a AutoColumn instance using the Read for a

Since: 0.0.0

Constructors

Readable a 

Instances

Instances details
Read a => AutoColumn (Readable a) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Errors

data Error Source #

Since: 0.0.0

Constructors

ErrorDuringProcessing ProcessorError

Occurs when processing the result table

ErrorDuringValidation ResultError

Occurs when validating the result object

Instances

Instances details
Eq Error Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Show Error Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Exception Error Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Monad m => MonadError Errors (QueryT m) Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Query

Methods

throwError :: Errors -> QueryT m a #

catchError :: QueryT m a -> (Errors -> QueryT m a) -> QueryT m a #

data ProcessorError Source #

Error that may occur during processing

Since: 0.0.0

data ResultError Source #

Error that occurs when validating the result

Since: 0.0.0

Instances

Instances details
Eq ResultError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Ord ResultError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Show ResultError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

data ParserError Source #

Error that occurs when parsing a column

Since: 0.0.0

Instances

Instances details
Eq ParserError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Ord ParserError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Show ParserError Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Common types

data Format #

Constructors

Text 
Binary 

Instances

Instances details
Enum Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Eq Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

data Oid #

Instances

Instances details
Eq Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

(==) :: Oid -> Oid -> Bool #

(/=) :: Oid -> Oid -> Bool #

Ord Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

compare :: Oid -> Oid -> Ordering #

(<) :: Oid -> Oid -> Bool #

(<=) :: Oid -> Oid -> Bool #

(>) :: Oid -> Oid -> Bool #

(>=) :: Oid -> Oid -> Bool #

max :: Oid -> Oid -> Oid #

min :: Oid -> Oid -> Oid #

Read Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

Storable Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

sizeOf :: Oid -> Int #

alignment :: Oid -> Int #

peekElemOff :: Ptr Oid -> Int -> IO Oid #

pokeElemOff :: Ptr Oid -> Int -> Oid -> IO () #

peekByteOff :: Ptr b -> Int -> IO Oid #

pokeByteOff :: Ptr b -> Int -> Oid -> IO () #

peek :: Ptr Oid -> IO Oid #

poke :: Ptr Oid -> Oid -> IO () #

AutoColumn Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Param Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Oid -> Value) Source #

data ColumnNum Source #

Numberic column identifier

Since: 0.0.0

Instances

Instances details
Bounded ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Enum ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Eq ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Integral ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Num ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Ord ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Read ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Real ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

Show ColumnNum Source # 
Instance details

Defined in PostgreSQL.Types

data RowNum Source #

Numberic row identifier

Since: 0.0.0

Instances

Instances details
Bounded RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Enum RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Eq RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Methods

(==) :: RowNum -> RowNum -> Bool #

(/=) :: RowNum -> RowNum -> Bool #

Integral RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Num RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Ord RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Read RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Real RowNum Source # 
Instance details

Defined in PostgreSQL.Types

Show RowNum Source # 
Instance details

Defined in PostgreSQL.Types

data Value Source #

Value

Since: 0.0.0

Constructors

Null 
Value ByteString 

Instances

Instances details
Eq Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

fromString :: String -> Value #

Param Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Value -> Value) Source #

data RawValue Source #

The raw cell value

Since: 0.0.0

Instances

Instances details
Eq RawValue Source # 
Instance details

Defined in PostgreSQL.Result.Column

Ord RawValue Source # 
Instance details

Defined in PostgreSQL.Result.Column

Show RawValue Source # 
Instance details

Defined in PostgreSQL.Result.Column

AutoColumn RawValue Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column