| Copyright | (c) 2011 MailRank Inc. (c) 2011-2012 Leon P Smith | 
|---|---|
| License | BSD3 | 
| Maintainer | Leon P Smith <leon@melding-monads.com> | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.PostgreSQL.Simple.Types
Description
Basic types.
Synopsis
- data Null = Null
- data Default = Default
- newtype Only a = Only {- fromOnly :: a
 
- newtype In a = In a
- newtype Binary a = Binary {- fromBinary :: a
 
- newtype Identifier = Identifier {}
- data QualifiedIdentifier = QualifiedIdentifier (Maybe Text) Text
- newtype Query = Query {}
- newtype Oid = Oid CUInt
- data h :. t = h :. t
- newtype Savepoint = Savepoint Query
- newtype PGArray a = PGArray {- fromPGArray :: [a]
 
- data Values a = Values [QualifiedIdentifier] [a]
Documentation
A placeholder for the SQL NULL value.
Constructors
| Null | 
A placeholder for the PostgreSQL DEFAULT value.
Constructors
| Default | 
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) -> {- ... -}Instances
| Functor Only | |
| Eq a => Eq (Only a) | |
| Data a => Data (Only a) | |
| 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 :: forall r r'. (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) | |
| Read a => Read (Only a) | |
| Show a => Show (Only a) | |
| Generic (Only a) | |
| NFData a => NFData (Only a) | |
| Defined in Data.Tuple.Only | |
| ToField a => ToRow (Only a) Source # | |
| FromField a => FromRow (Maybe (Only a)) Source # | |
| FromField a => FromRow (Only a) Source # | |
| type Rep (Only a) | |
| Defined in Data.Tuple.Only | |
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:
- Use postgresql-simple's - Valuestype 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)))
- Use sql's - COALESCEoperator to turn a logical- nullinto 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 - COALESCEoperator, so if you have an index on- idthen you probably don't want to write the last example with- COALESCE, which would result in a table scan. There are further caveats if- idcan be null or you want null treated sensibly as a component of- INor- NOT IN.
Constructors
| In a | 
Wrap binary data for use as a bytea value.
Constructors
| Binary | |
| Fields 
 | |
Instances
| Functor Binary Source # | |
| Eq a => Eq (Binary a) Source # | |
| Ord a => Ord (Binary a) Source # | |
| Defined in Database.PostgreSQL.Simple.Types | |
| Read a => Read (Binary a) Source # | |
| Show a => Show (Binary a) Source # | |
| ToField (Binary ByteString) Source # | |
| Defined in Database.PostgreSQL.Simple.ToField | |
| ToField (Binary ByteString) Source # | |
| Defined in Database.PostgreSQL.Simple.ToField | |
| FromField (Binary ByteString) Source # | bytea | 
| Defined in Database.PostgreSQL.Simple.FromField Methods | |
| FromField (Binary ByteString) Source # | bytea | 
| Defined in Database.PostgreSQL.Simple.FromField Methods | |
newtype Identifier Source #
Wrap text for use as sql identifier, i.e. a table or column name.
Constructors
| Identifier | |
| Fields | |
Instances
data QualifiedIdentifier Source #
Wrap text for use as (maybe) qualified identifier, i.e. a table with schema, or column with table.
Constructors
| QualifiedIdentifier (Maybe Text) Text | 
Instances
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.
Constructors
| Query | |
| Fields | |
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) Source # | |
| (Ord h, Ord t) => Ord (h :. t) Source # | |
| Defined in Database.PostgreSQL.Simple.Types | |
| (Read h, Read t) => Read (h :. t) Source # | |
| (Show h, Show t) => Show (h :. t) Source # | |
| (ToRow a, ToRow b) => ToRow (a :. b) Source # | |
| (FromRow a, FromRow b) => FromRow (a :. b) Source # | |
Instances
| Eq Savepoint Source # | |
| Ord Savepoint Source # | |
| Defined in Database.PostgreSQL.Simple.Types | |
| Read Savepoint Source # | |
| Show Savepoint Source # | |
Wrap a list for use as a PostgreSQL array.
Constructors
| PGArray | |
| Fields 
 | |
Instances
| Functor PGArray Source # | |
| Eq a => Eq (PGArray a) Source # | |
| Ord a => Ord (PGArray a) Source # | |
| Defined in Database.PostgreSQL.Simple.Types | |
| Read a => Read (PGArray a) Source # | |
| Show a => Show (PGArray a) Source # | |
| ToField a => ToField (PGArray a) Source # | |
| (FromField a, Typeable a) => FromField (PGArray a) Source # | any postgresql array whose elements are compatible with type  | 
| Defined in Database.PostgreSQL.Simple.FromField Methods fromField :: FieldParser (PGArray a) Source # | |
Represents a VALUES table literal,  usable as an alternative to
   executeMany and
   returning.  The main advantage is that
   you can parametrize more than just a single VALUES expression.
   For example,  here's a query to insert a thing into one table
   and some attributes of that thing into another,   returning the
   new id generated by the database:
query c [sql|
    WITH new_thing AS (
      INSERT INTO thing (name) VALUES (?) RETURNING id
    ), new_attributes AS (
      INSERT INTO thing_attributes
         SELECT new_thing.id, attrs.*
           FROM new_thing JOIN ? attrs ON TRUE
    ) SELECT * FROM new_thing
 |] ("foo", Values [  "int4", "text"    ]
                   [ ( 1    , "hello" )
                   , ( 2    , "world" ) ])(Note this example uses writable common table expressions, which were added in PostgreSQL 9.1)
The second parameter gets expanded into the following SQL syntax:
(VALUES (1::"int4",'hello'::"text"),(2,'world'))
When the list of attributes is empty, the second parameter expands to:
(VALUES (null::"int4",null::"text") LIMIT 0)
By contrast, executeMany and returning don't issue the query
   in the empty case, and simply return 0 and [] respectively.
   This behavior is usually correct given their intended use cases,
   but would certainly be wrong in the example above.
The first argument is a list of postgresql type names.  Because this
   is turned into a properly quoted identifier,  the type name is case
   sensitive and must be as it appears in the pg_type table.   Thus,
   you must write timestamptz instead of timestamp with time zone,
   int4 instead of integer or serial, _int8 instead of bigint[],
   etcetera.
You may omit the type names,  however,  if you do so the list
   of values must be non-empty,  and postgresql must be able to infer
   the types of the columns from the surrounding context.   If the first
   condition is not met,  postgresql-simple will throw an exception
   without issuing the query.   In the second case,  the postgres server
   will return an error which will be turned into a SqlError exception.
See https://www.postgresql.org/docs/9.5/static/sql-values.html for more information.
Constructors
| Values [QualifiedIdentifier] [a] |