snaplet-postgresql-simple-1.2.0.0: postgresql-simple snaplet for the Snap Framework

Safe HaskellNone
LanguageHaskell2010

Snap.Snaplet.PostgresqlSimple

Contents

Description

This snaplet makes it simple to use a PostgreSQL database from your Snap application and is based on the excellent postgresql-simple library (http://hackage.haskell.org/package/postgresql-simple) by Leon Smith (adapted from Bryan O'Sullivan's mysql-simple). Now, adding a database to your web app takes just two simple steps.

First, include this snaplet in your application's state.

data App = App
    { ... -- Other state needed in your app
    , _db :: Snaplet Postgres
    }

Next, call the pgsInit from your application's initializer.

appInit = makeSnaplet ... $ do
    ...
    d <- nestSnaplet "db" db pgsInit
    return $ App ... d

Now you can use any of the postgresql-simple wrapper functions defined in this module anywhere in your application handlers. For instance:

postHandler :: Handler App App ()
postHandler = do
    posts <- with db $ query_ "select * from blog_post"
    ...

Optionally, if you find yourself doing many database queries, you can eliminate some of the boilerplate by defining a HasPostgres instance for your application.

instance HasPostgres (Handler b App) where
  getPostgresState = with db get
  setLocalPostgresState s = local (set (db . snapletValue) s)

With this code, our postHandler example no longer requires the with function:

postHandler :: Handler App App ()
postHandler = do
    posts <- query_ "select * from blog_post"
    ...

If you have code that runs multiple queries but you want to make sure that you only use one database connection then you can use the withPG function, like so:

postHandler :: Handler App App ()
postHandler = withPG $ do
    posts <- query_ "select * from blog_post"
    links <- query_ "select * from links"
    ...

The first time you run an application with the postgresql-simple snaplet, a configuration file devel.cfg is created in the snaplets/postgresql-simple directory underneath your project root. It specifies how to connect to your PostgreSQL server and what user, password, and database to use. Edit this file and modify the values appropriately and you'll be off and running.

If you want to have out-of-the-box authentication, look at the documentation for the Snap.Snaplet.Auth.Backends.PostgresqlSimple module.

Synopsis

The Snaplet

data Postgres Source #

The state for the postgresql-simple snaplet. To use it in your app include this in your application state and use pgsInit to initialize it.

Instances
HasPostgres (Handler b Postgres) Source #

Default instance

Instance details

Defined in Snap.Snaplet.PostgresqlSimple

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT (Snaplet Postgres) m) Source #

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

d <- nestSnaplet "db" db pgsInit
count <- liftIO $ runReaderT (execute "INSERT ..." params) d
Instance details

Defined in Snap.Snaplet.PostgresqlSimple

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT Postgres m) Source #

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

Instance details

Defined in Snap.Snaplet.PostgresqlSimple

class (MonadIO m, MonadBaseControl IO m) => HasPostgres m where Source #

Instantiate this typeclass on 'Handler b YourAppState' so this snaplet can find the connection source. If you need to have multiple instances of the postgres snaplet in your application, then don't provide this instance and leverage the default instance by using "with dbLens" in front of calls to snaplet-postgresql-simple functions.

Instances
HasPostgres m => HasPostgres (MaybeT m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

HasPostgres m => HasPostgres (IdentityT m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

HasPostgres m => HasPostgres (StateT w m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

(Monoid w, HasPostgres m) => HasPostgres (WriterT w m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

HasPostgres m => HasPostgres (StateT w m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

(Monoid w, HasPostgres m) => HasPostgres (WriterT w m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

HasPostgres (Handler b Postgres) Source #

Default instance

Instance details

Defined in Snap.Snaplet.PostgresqlSimple

HasPostgres m => HasPostgres (ReaderT r m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT (Snaplet Postgres) m) Source #

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

d <- nestSnaplet "db" db pgsInit
count <- liftIO $ runReaderT (execute "INSERT ..." params) d
Instance details

Defined in Snap.Snaplet.PostgresqlSimple

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT Postgres m) Source #

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

Instance details

Defined in Snap.Snaplet.PostgresqlSimple

(Monoid w, HasPostgres m) => HasPostgres (RWST r w s m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

Methods

getPostgresState :: RWST r w s m Postgres Source #

setLocalPostgresState :: Postgres -> RWST r w s m a -> RWST r w s m a Source #

(Monoid w, HasPostgres m) => HasPostgres (RWST r w s m) Source # 
Instance details

Defined in Snap.Snaplet.PostgresqlSimple.Internal

Methods

getPostgresState :: RWST r w s m Postgres Source #

setLocalPostgresState :: Postgres -> RWST r w s m a -> RWST r w s m a Source #

data PGSConfig Source #

Data type holding all the snaplet's config information.

Constructors

PGSConfig 

Fields

  • pgsConnStr :: ByteString

    A libpq connection string.

  • pgsNumStripes :: Int

    The number of distinct sub-pools to maintain. The smallest acceptable value is 1.

  • pgsIdleTime :: Double

    Amount of time for which an unused resource is kept open. The smallest acceptable value is 0.5 seconds.

  • pgsResources :: Int

    Maximum number of resources to keep open per stripe. The smallest acceptable value is 1.

pgsDefaultConfig Source #

Arguments

:: ByteString

A connection string such as "host=localhost port=5432 dbname=mydb"

-> PGSConfig 

Returns a config object with default values and the specified connection string.

mkPGSConfig :: MonadIO m => Config -> m PGSConfig Source #

Builds a PGSConfig object from a configurator Config object. This function uses getConnectionString to construct the connection string. The rest of the PGSConfig fields are obtained from "numStripes", "idleTime", and "maxResourcesPerStripe".

pgsInit :: SnapletInit b Postgres Source #

Initialize the snaplet

pgsInit' :: PGSConfig -> SnapletInit b Postgres Source #

Initialize the snaplet using a specific configuration.

getConnectionString :: Config -> IO ByteString Source #

Produce a connection string from a config

withPG :: HasPostgres m => m b -> m b Source #

Function that reserves a single connection for the duration of the given action. Nested calls to withPG will only reserve one connection. For example, the following code calls withPG twice in a nested way yet only results in a single connection being reserved:

myHandler = withPG $ do
   queryTheDatabase
   commonDatabaseMethod

commonDatabaseMethod = withPG $ do
   moreDatabaseActions
   evenMoreDatabaseActions

This is useful in a practical setting because you may often find yourself in a situation where you have common code (that requires a database connection) that you wish to call from other blocks of code that may require a database connection and you still want to make sure that you are only using one connection through all of your nested methods.

data Connection #

Instances
Eq Connection 
Instance details

Defined in Database.PostgreSQL.Simple.Internal

liftPG :: HasPostgres m => (Connection -> m a) -> m a Source #

Convenience function for executing a function that needs a database connection.

liftPG' :: HasPostgres m => (Connection -> IO b) -> m b Source #

Convenience function for executing a function that needs a database connection specialized to IO.

Wrappers and re-exports

query :: (HasPostgres m, ToRow q, FromRow r) => Query -> q -> m [r] Source #

See query

query_ :: (HasPostgres m, FromRow r) => Query -> m [r] Source #

See query_

fold :: (HasPostgres m, FromRow row, ToRow params) => Query -> params -> b -> (b -> row -> IO b) -> m b Source #

 

foldWithOptions :: (HasPostgres m, FromRow row, ToRow params) => FoldOptions -> Query -> params -> b -> (b -> row -> IO b) -> m b Source #

 

fold_ :: (HasPostgres m, FromRow row) => Query -> b -> (b -> row -> IO b) -> m b Source #

 

foldWithOptions_ :: (HasPostgres m, FromRow row) => FoldOptions -> Query -> b -> (b -> row -> IO b) -> m b Source #

 

forEach :: (HasPostgres m, FromRow r, ToRow q) => Query -> q -> (r -> IO ()) -> m () Source #

 

forEach_ :: (HasPostgres m, FromRow r) => Query -> (r -> IO ()) -> m () Source #

 

execute :: (HasPostgres m, ToRow q) => Query -> q -> m Int64 Source #

 

executeMany :: (HasPostgres m, ToRow q) => Query -> [q] -> m Int64 Source #

 

returning :: (HasPostgres m, ToRow q, FromRow r) => Query -> [q] -> m [r] Source #

withTransaction :: HasPostgres m => m a -> m a Source #

Be careful that you do not call Snap's finishWith function anywhere inside the function that you pass to withTransaction. Doing so has been known to cause DB connection leaks.

withTransactionLevel :: HasPostgres m => IsolationLevel -> m a -> m a Source #

Be careful that you do not call Snap's finishWith function anywhere inside the function that you pass to withTransactionLevel. Doing so has been known to cause DB connection leaks.

withTransactionMode :: HasPostgres m => TransactionMode -> m a -> m a Source #

Be careful that you do not call Snap's finishWith function anywhere inside the function that you pass to withTransactionMode. Doing so has been known to cause DB connection leaks.

withTransactionEither :: HasPostgres m => m (Either a b) -> m (Either a b) Source #

Be careful that you do not call Snap's finishWith function anywhere inside the function that you pass to withTransactionMode. Doing so has been known to cause DB connection leaks.

withTransactionModeEither :: HasPostgres m => TransactionMode -> m (Either a b) -> m (Either a b) Source #

Be careful that you do not call Snap's finishWith function anywhere inside the function that you pass to withTransactionMode. Doing so has been known to cause DB connection leaks.

data Query #

A query string. This type is intended to make it difficult to construct a SQL query by concatenating string fragments, as that is an extremely common way to accidentally introduce SQL injection vulnerabilities into an application.

This type is an instance of IsString, so the easiest way to construct a query is to enable the OverloadedStrings language extension and then simply write the query in double quotes.

{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple

q :: Query
q = "select ?"

The underlying type is a ByteString, and literal Haskell strings that contain Unicode characters will be correctly transformed to UTF-8.

Instances
Eq Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Ord Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: Query -> Query -> Ordering #

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

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

(>) :: Query -> Query -> Bool #

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

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Read Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

fromString :: String -> Query #

Semigroup Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Monoid Query 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

newtype In a #

Wrap a list of values for use in an IN clause. Replaces a single "?" character with a parenthesized list of rendered values.

Example:

query c "select * from whatever where id in ?" (Only (In [3,4,5]))

Note that In [] expands to (null), which works as expected in the query above, but evaluates to the logical null value on every row instead of TRUE. This means that changing the query above to ... id NOT in ? and supplying the empty list as the parameter returns zero rows, instead of all of them as one would expect.

Since postgresql doesn't seem to provide a syntax for actually specifying an empty list, which could solve this completely, there are two workarounds particularly worth mentioning, namely:

  1. Use postgresql-simple's Values type instead, which can handle the empty case correctly. Note however that while specifying the postgresql type "int4" is mandatory in the empty case, specifying the haskell type Values (Only Int) would not normally be needed in realistic use cases.

    query c "select * from whatever where id not in ?"
            (Only (Values ["int4"] [] :: Values (Only Int)))
  2. Use sql's COALESCE operator to turn a logical null into the correct boolean. Note however that the correct boolean depends on the use case:

    query c "select * from whatever where coalesce(id NOT in ?, TRUE)"
            (Only (In [] :: In [Int]))
    query c "select * from whatever where coalesce(id IN ?, FALSE)"
            (Only (In [] :: In [Int]))

    Note that at as of PostgreSQL 9.4, the query planner cannot see inside the COALESCE operator, so if you have an index on id then you probably don't want to write the last example with COALESCE, which would result in a table scan. There are further caveats if id can be null or you want null treated sensibly as a component of IN or NOT IN.

Constructors

In a 
Instances
Functor In 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Eq a => Eq (In a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: In a -> In a -> Bool #

(/=) :: In a -> In a -> Bool #

Ord a => Ord (In a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: In a -> In a -> Ordering #

(<) :: In a -> In a -> Bool #

(<=) :: In a -> In a -> Bool #

(>) :: In a -> In a -> Bool #

(>=) :: In a -> In a -> Bool #

max :: In a -> In a -> In a #

min :: In a -> In a -> In a #

Read a => Read (In a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (In a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> In a -> ShowS #

show :: In a -> String #

showList :: [In a] -> ShowS #

ToField a => ToField (In [a]) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

Methods

toField :: In [a] -> Action #

newtype Binary a #

Wrap binary data for use as a bytea value.

Constructors

Binary 

Fields

Instances
Functor Binary 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

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

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

Eq a => Eq (Binary a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: Binary a -> Binary a -> Bool #

(/=) :: Binary a -> Binary a -> Bool #

Ord a => Ord (Binary a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: Binary a -> Binary a -> Ordering #

(<) :: Binary a -> Binary a -> Bool #

(<=) :: Binary a -> Binary a -> Bool #

(>) :: Binary a -> Binary a -> Bool #

(>=) :: Binary a -> Binary a -> Bool #

max :: Binary a -> Binary a -> Binary a #

min :: Binary a -> Binary a -> Binary a #

Read a => Read (Binary a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Show a => Show (Binary a) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> Binary a -> ShowS #

show :: Binary a -> String #

showList :: [Binary a] -> ShowS #

FromField (Binary ByteString)

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField (Binary ByteString)

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ToField (Binary ByteString) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

ToField (Binary ByteString) 
Instance details

Defined in Database.PostgreSQL.Simple.ToField

newtype Only a #

The 1-tuple type or single-value "collection".

This type is structurally equivalent to the Identity type, but its intent is more about serving as the anonymous 1-tuple type missing from Haskell for attaching typeclass instances.

Parameter usage example:

encodeSomething (Only (42::Int))

Result usage example:

xs <- decodeSomething
forM_ xs $ \(Only id) -> {- ... -}

Constructors

Only 

Fields

Instances
Functor Only 
Instance details

Defined in Data.Tuple.Only

Methods

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

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

Eq a => Eq (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Data a => Data (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) #

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) #

gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

Ord a => Ord (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) 
Instance details

Defined in Data.Tuple.Only

Show a => Show (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

NFData a => NFData (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

rnf :: Only a -> () #

FromField a => FromRow (Maybe (Only a)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Only a)) #

FromField a => FromRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Only a) #

ToField a => ToRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: Only a -> [Action] #

type Rep (Only a) 
Instance details

Defined in Data.Tuple.Only

type Rep (Only a) = D1 (MetaData "Only" "Data.Tuple.Only" "Only-0.1-4eYnxvcrr7tEbYgCvIkHLb" True) (C1 (MetaCons "Only" PrefixI True) (S1 (MetaSel (Just "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data FormatError #

Exception thrown if a Query could not be formatted correctly. This may occur if the number of '?' characters in the query string does not match the number of parameters provided.

Constructors

FormatError 

data QueryError #

Exception thrown if query is used to perform an INSERT-like operation, or execute is used to perform a SELECT-like operation.

Constructors

QueryError 

Fields

data ResultError #

Exception thrown if conversion from a SQL value to a Haskell value fails.

Constructors

Incompatible

The SQL and Haskell types are not compatible.

UnexpectedNull

A SQL NULL was encountered when the Haskell type did not permit it.

ConversionFailed

The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row).

data IsolationLevel #

Of the four isolation levels defined by the SQL standard, these are the three levels distinguished by PostgreSQL as of version 9.0. See https://www.postgresql.org/docs/9.5/static/transaction-iso.html for more information. Note that prior to PostgreSQL 9.0, RepeatableRead was equivalent to Serializable.

Constructors

DefaultIsolationLevel

the isolation level will be taken from PostgreSQL's per-connection default_transaction_isolation variable, which is initialized according to the server's config. The default configuration is ReadCommitted.

ReadCommitted 
RepeatableRead 
Serializable 
Instances
Bounded IsolationLevel 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Enum IsolationLevel 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Eq IsolationLevel 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Ord IsolationLevel 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Show IsolationLevel 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

data ReadWriteMode #

Constructors

DefaultReadWriteMode

the read-write mode will be taken from PostgreSQL's per-connection default_transaction_read_only variable, which is initialized according to the server's config. The default configuration is ReadWrite.

ReadWrite 
ReadOnly 
Instances
Bounded ReadWriteMode 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Enum ReadWriteMode 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Eq ReadWriteMode 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Ord ReadWriteMode 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

Show ReadWriteMode 
Instance details

Defined in Database.PostgreSQL.Simple.Transaction

begin :: Connection -> IO () #

Begin a transaction.

beginLevel :: IsolationLevel -> Connection -> IO () #

Begin a transaction with a given isolation level

beginMode :: TransactionMode -> Connection -> IO () #

Begin a transaction with a given transaction mode

rollback :: Connection -> IO () #

Rollback a transaction.

commit :: Connection -> IO () #

Commit a transaction.

data h :. t infixr 3 #

A composite type to parse your custom data structures without having to define dummy newtype wrappers every time.

instance FromRow MyData where ...
instance FromRow MyData2 where ...

then I can do the following for free:

res <- query' c "..."
forM res $ \(MyData{..} :. MyData2{..}) -> do
  ....

Constructors

h :. t infixr 3 
Instances
(Eq h, Eq t) => Eq (h :. t) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

(==) :: (h :. t) -> (h :. t) -> Bool #

(/=) :: (h :. t) -> (h :. t) -> Bool #

(Ord h, Ord t) => Ord (h :. t) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

compare :: (h :. t) -> (h :. t) -> Ordering #

(<) :: (h :. t) -> (h :. t) -> Bool #

(<=) :: (h :. t) -> (h :. t) -> Bool #

(>) :: (h :. t) -> (h :. t) -> Bool #

(>=) :: (h :. t) -> (h :. t) -> Bool #

max :: (h :. t) -> (h :. t) -> h :. t #

min :: (h :. t) -> (h :. t) -> h :. t #

(Read h, Read t) => Read (h :. t) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

readsPrec :: Int -> ReadS (h :. t) #

readList :: ReadS [h :. t] #

readPrec :: ReadPrec (h :. t) #

readListPrec :: ReadPrec [h :. t] #

(Show h, Show t) => Show (h :. t) 
Instance details

Defined in Database.PostgreSQL.Simple.Types

Methods

showsPrec :: Int -> (h :. t) -> ShowS #

show :: (h :. t) -> String #

showList :: [h :. t] -> ShowS #

(FromRow a, FromRow b) => FromRow (a :. b) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a :. b) #

(ToRow a, ToRow b) => ToRow (a :. b) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a :. b) -> [Action] #

class ToRow a where #

A collection type that can be turned into a list of rendering Actions.

Instances should use the toField method of the ToField class to perform conversion of each element of the collection.

You can derive ToRow for your data type using GHC generics, like this:

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric  #-}

import GHC.Generics (Generic)
import Database.PostgreSQL.Simple (ToRow)

data User = User { name :: String, fileQuota :: Int }
  deriving (Generic, ToRow)

Note that this only works for product types (e.g. records) and does not support sum types or recursive types.

Minimal complete definition

Nothing

Methods

toRow :: a -> [Action] #

Instances
ToRow () 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: () -> [Action] #

ToField a => ToRow [a] 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: [a] -> [Action] #

ToField a => ToRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: Only a -> [Action] #

(ToField a, ToField b) => ToRow (a, b) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b) -> [Action] #

(ToRow a, ToRow b) => ToRow (a :. b) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a :. b) -> [Action] #

(ToField a, ToField b, ToField c) => ToRow (a, b, c) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c) -> [Action] #

(ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h) => ToRow (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i) => ToRow (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j) => ToRow (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k) => ToRow (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r, ToField s) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> [Action] #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j, ToField k, ToField l, ToField m, ToField n, ToField o, ToField p, ToField q, ToField r, ToField s, ToField t) => ToRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Instance details

Defined in Database.PostgreSQL.Simple.ToRow

Methods

toRow :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> [Action] #

class FromRow a where #

A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.

Note that instances can be defined outside of postgresql-simple, which is often useful. For example, here's an instance for a user-defined pair:

data User = User { name :: String, fileQuota :: Int }

instance FromRow User where
    fromRow = User <$> field <*> field

The number of calls to field must match the number of fields returned in a single row of the query result. Otherwise, a ConversionFailed exception will be thrown.

You can also derive FromRow for your data type using GHC generics, like this:

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric  #-}

import GHC.Generics (Generic)
import Database.PostgreSQL.Simple (FromRow)

data User = User { name :: String, fileQuota :: Int }
  deriving (Generic, FromRow)

Note that this only works for product types (e.g. records) and does not support sum types or recursive types.

Note that field evaluates its result to WHNF, so the caveats listed in mysql-simple and very early versions of postgresql-simple no longer apply. Instead, look at the caveats associated with user-defined implementations of fromField.

Minimal complete definition

Nothing

Methods

fromRow :: RowParser a #

Instances
FromRow AuthUser Source # 
Instance details

Defined in Snap.Snaplet.Auth.Backends.PostgresqlSimple

FromField a => FromRow [a] 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser [a] #

FromField a => FromRow (Maybe [a]) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe [a]) #

(FromField a, FromField b) => FromRow (Maybe (a, b)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b)) #

(FromField a, FromField b, FromField c) => FromRow (Maybe (a, b, c)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c)) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (Maybe (a, b, c, d)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d)) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (Maybe (a, b, c, d, e)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (Maybe (a, b, c, d, e, f)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (Maybe (a, b, c, d, e, f, g)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (Maybe (a, b, c, d, e, f, g, h)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (Maybe (a, b, c, d, e, f, g, h, i)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s, FromField t) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) #

FromField a => FromRow (Maybe (Only a)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Only a)) #

FromField a => FromRow (Maybe (Vector a)) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Maybe (Vector a)) #

FromField a => FromRow (Only a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Only a) #

FromField a => FromRow (Vector a) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (Vector a) #

(FromField a, FromField b) => FromRow (a, b) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b) #

(FromRow a, FromRow b) => FromRow (a :. b) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a :. b) #

(FromField a, FromField b, FromField c) => FromRow (a, b, c) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k) => FromRow (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j, FromField k, FromField l, FromField m, FromField n, FromField o, FromField p, FromField q, FromField r, FromField s, FromField t) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Instance details

Defined in Database.PostgreSQL.Simple.FromRow

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) #

defaultConnectInfo :: ConnectInfo #

Default information for setting up a connection.

Defaults are as follows:

  • Server on localhost
  • Port on 5432
  • User postgres
  • No password
  • Database postgres

Use as in the following example:

connect defaultConnectInfo { connectHost = "db.example.com" }

Orphan instances

HasPostgres (Handler b Postgres) Source #

Default instance

Instance details

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT (Snaplet Postgres) m) Source #

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

d <- nestSnaplet "db" db pgsInit
count <- liftIO $ runReaderT (execute "INSERT ..." params) d
Instance details

(MonadIO m, MonadBaseControl IO m) => HasPostgres (ReaderT Postgres m) Source #

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

Instance details