nri-postgresql-0.1.0.3: Make queries against Postgresql.
Safe HaskellNone
LanguageHaskell2010

Postgres

Description

Functions for running Postgres queries.

Synopsis

Documentation

data Connection Source #

A connection to Postgres. You need this for making Postgres queries.

data Settings Source #

Postgres connection details. You can use decoder to create one of these.

Instances

Instances details
Eq Settings Source # 
Instance details

Defined in Postgres.Settings

Show Settings Source # 
Instance details

Defined in Postgres.Settings

decoder :: Decoder Settings Source #

Create a Settings value by reading settings from environment values.

environment variable
PGHOST
default value
localhost
environment variable
PGPORT
default value
5432
environment variable
PGDATABASE
default value
postgresql
environment variable
PGUSER
default value
postgresql
environment variable
PGPASSWORD
default value
environment variable
PG_POOL_SIZE
default value
500
environment variable
PG_POOL_STRIPES
default value
1
environment variable
PG_POOL_MAX_IDLE_TIME
default value
3600
environment variable
PG_QUERY_TIMEOUT_SECONDS
default value
5

data Query row Source #

A Postgres query. Create one of these using the sql quasiquoter.

data Error Source #

A postgres query might fail with one of these errors.

Constructors

Timeout Float 
UniqueViolation Text 
Other Text [Context] 

Instances

Instances details
Show Error Source # 
Instance details

Defined in Postgres.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Exception Error Source # 
Instance details

Defined in Postgres.Error

sql :: QuasiQuoter Source #

Quasi-quoter that allows you to write plain SQL in your code. The query is checked at compile-time using the 'postgresql-typed' library.

Requires the QuasiQuotes language extension to be enabled.

[sql| SELECT name, breed FROM doggos |]

doQuery :: HasCallStack => Connection -> Query row -> (Result Error [row] -> Task e a) -> Task e a Source #

Run a query against MySql. This will return a list of rows, where the row type is a tuple containing the queried columns.

doQuery
  connection
  [sql| SELECT name, breed FROM doggos |]
  (\result ->
    case result of
      Ok rows -> Task.succeed rows
      Err err -> Task.fail err
  )

transaction :: Connection -> (Connection -> Task e a) -> Task e a Source #

Perform a database transaction.

inTestTransaction :: Connection -> (Connection -> Task x a) -> Task x a Source #

Run code in a transaction, then roll that transaction back. Useful in tests that shouldn't leave anything behind in the DB.

class PGType t => PGColumn (t :: Symbol) a where #

A PGColumn t a instance describes how te decode a PostgreSQL type t to a.

Methods

pgDecode :: PGTypeID t -> PGTextValue -> a #

Decode the PostgreSQL text representation into a value.

Instances

Instances details
PGStringType t => PGColumn t String 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> String #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> String #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> String #

PGStringType t => PGColumn t Text 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Text #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Text #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Text #

PGStringType t => PGColumn t Text 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Text #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Text #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Text #

PGType t => PGColumn t PGValue 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGValue #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGValue #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGValue #

PGRecordType t => PGColumn t PGRecord 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGRecord #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGRecord #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGRecord #

PGStringType t => PGColumn t PGName 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> PGName #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> PGName #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> PGName #

PGStringType t => PGColumn t ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> ByteString #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> ByteString #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> ByteString #

PGStringType t => PGColumn t ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> ByteString #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> ByteString #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> ByteString #

PGColumn "\"char\"" Char 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "\"char\"" -> PGTextValue -> Char #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "\"char\"" -> PGBinaryValue -> Char #

pgDecodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> PGValue -> Char #

PGColumn "\"char\"" Word8 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "\"char\"" -> PGTextValue -> Word8 #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "\"char\"" -> PGBinaryValue -> Word8 #

pgDecodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> PGValue -> Word8 #

PGColumn "bigint" Int64 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bigint" -> PGTextValue -> Int64 #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bigint" -> PGBinaryValue -> Int64 #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bigint" -> PGValue -> Int64 #

PGColumn "boolean" Bool 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "boolean" -> PGTextValue -> Bool #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "boolean" -> PGBinaryValue -> Bool #

pgDecodeValue :: PGTypeEnv -> PGTypeID "boolean" -> PGValue -> Bool #

PGColumn "bytea" ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bytea" -> PGTextValue -> ByteString #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bytea" -> PGBinaryValue -> ByteString #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bytea" -> PGValue -> ByteString #

PGColumn "bytea" ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "bytea" -> PGTextValue -> ByteString #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "bytea" -> PGBinaryValue -> ByteString #

pgDecodeValue :: PGTypeEnv -> PGTypeID "bytea" -> PGValue -> ByteString #

PGColumn "date" Day 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "date" -> PGTextValue -> Day #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "date" -> PGBinaryValue -> Day #

pgDecodeValue :: PGTypeEnv -> PGTypeID "date" -> PGValue -> Day #

PGColumn "double precision" Double 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "double precision" -> PGTextValue -> Double #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "double precision" -> PGBinaryValue -> Double #

pgDecodeValue :: PGTypeEnv -> PGTypeID "double precision" -> PGValue -> Double #

PGColumn "integer" Int32 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "integer" -> PGTextValue -> Int32 #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "integer" -> PGBinaryValue -> Int32 #

pgDecodeValue :: PGTypeEnv -> PGTypeID "integer" -> PGValue -> Int32 #

PGColumn "interval" DiffTime

Representation of DiffTime as interval. PostgreSQL stores months and days separately in intervals, but DiffTime does not. We collapse all interval fields into seconds

Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "interval" -> PGTextValue -> DiffTime #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "interval" -> PGBinaryValue -> DiffTime #

pgDecodeValue :: PGTypeEnv -> PGTypeID "interval" -> PGValue -> DiffTime #

PGColumn "json" Value 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "json" -> PGTextValue -> Value #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "json" -> PGBinaryValue -> Value #

pgDecodeValue :: PGTypeEnv -> PGTypeID "json" -> PGValue -> Value #

PGColumn "jsonb" Value 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "jsonb" -> PGTextValue -> Value #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "jsonb" -> PGBinaryValue -> Value #

pgDecodeValue :: PGTypeEnv -> PGTypeID "jsonb" -> PGValue -> Value #

PGColumn "numeric" Rational

High-precision representation of Rational as numeric. Unfortunately, numeric has an NaN, while Rational does not. NaN numeric values will produce exceptions.

Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "numeric" -> PGTextValue -> Rational #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "numeric" -> PGBinaryValue -> Rational #

pgDecodeValue :: PGTypeEnv -> PGTypeID "numeric" -> PGValue -> Rational #

PGColumn "numeric" Scientific 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "numeric" -> PGTextValue -> Scientific #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "numeric" -> PGBinaryValue -> Scientific #

pgDecodeValue :: PGTypeEnv -> PGTypeID "numeric" -> PGValue -> Scientific #

PGColumn "oid" OID 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "oid" -> PGTextValue -> OID #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "oid" -> PGBinaryValue -> OID #

pgDecodeValue :: PGTypeEnv -> PGTypeID "oid" -> PGValue -> OID #

PGColumn "real" Double 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "real" -> PGTextValue -> Double #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "real" -> PGBinaryValue -> Double #

pgDecodeValue :: PGTypeEnv -> PGTypeID "real" -> PGValue -> Double #

PGColumn "real" Float 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "real" -> PGTextValue -> Float #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "real" -> PGBinaryValue -> Float #

pgDecodeValue :: PGTypeEnv -> PGTypeID "real" -> PGValue -> Float #

PGColumn "smallint" Int16 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "smallint" -> PGTextValue -> Int16 #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "smallint" -> PGBinaryValue -> Int16 #

pgDecodeValue :: PGTypeEnv -> PGTypeID "smallint" -> PGValue -> Int16 #

PGColumn "time without time zone" TimeOfDay 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "time without time zone" -> PGTextValue -> TimeOfDay #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "time without time zone" -> PGBinaryValue -> TimeOfDay #

pgDecodeValue :: PGTypeEnv -> PGTypeID "time without time zone" -> PGValue -> TimeOfDay #

PGColumn "timestamp with time zone" UTCTime 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "timestamp with time zone" -> PGTextValue -> UTCTime #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> PGBinaryValue -> UTCTime #

pgDecodeValue :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> PGValue -> UTCTime #

PGColumn "timestamp without time zone" LocalTime 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "timestamp without time zone" -> PGTextValue -> LocalTime #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> PGBinaryValue -> LocalTime #

pgDecodeValue :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> PGValue -> LocalTime #

PGColumn "uuid" UUID 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "uuid" -> PGTextValue -> UUID #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "uuid" -> PGBinaryValue -> UUID #

pgDecodeValue :: PGTypeEnv -> PGTypeID "uuid" -> PGValue -> UUID #

PGColumn "void" () 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "void" -> PGTextValue -> () #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "void" -> PGBinaryValue -> () #

pgDecodeValue :: PGTypeEnv -> PGTypeID "void" -> PGValue -> () #

PGColumn t a => PGColumn t (Maybe a) 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID t -> PGTextValue -> Maybe a #

pgDecodeBinary :: PGTypeEnv -> PGTypeID t -> PGBinaryValue -> Maybe a #

pgDecodeValue :: PGTypeEnv -> PGTypeID t -> PGValue -> Maybe a #

PGColumn "time with time zone" (TimeOfDay, TimeZone) 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgDecode :: PGTypeID "time with time zone" -> PGTextValue -> (TimeOfDay, TimeZone) #

pgDecodeBinary :: PGTypeEnv -> PGTypeID "time with time zone" -> PGBinaryValue -> (TimeOfDay, TimeZone) #

pgDecodeValue :: PGTypeEnv -> PGTypeID "time with time zone" -> PGValue -> (TimeOfDay, TimeZone) #

class PGType t => PGParameter (t :: Symbol) a where #

A PGParameter t a instance describes how to encode a PostgreSQL type t from a.

Methods

pgEncode :: PGTypeID t -> a -> PGTextValue #

Encode a value to a PostgreSQL text representation.

Instances

Instances details
PGStringType t => PGParameter t String 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t Text 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID t -> Text -> PGTextValue #

pgLiteral :: PGTypeID t -> Text -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID t -> Text -> PGValue #

PGStringType t => PGParameter t Text 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID t -> Text -> PGTextValue #

pgLiteral :: PGTypeID t -> Text -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID t -> Text -> PGValue #

PGRecordType t => PGParameter t PGRecord 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t PGName 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGStringType t => PGParameter t ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

PGParameter "\"char\"" Char 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "\"char\"" -> Char -> PGTextValue #

pgLiteral :: PGTypeID "\"char\"" -> Char -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> Char -> PGValue #

PGParameter "\"char\"" Word8 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "\"char\"" -> Word8 -> PGTextValue #

pgLiteral :: PGTypeID "\"char\"" -> Word8 -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "\"char\"" -> Word8 -> PGValue #

PGParameter "any" PGValue 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "any" -> PGValue -> PGTextValue #

pgLiteral :: PGTypeID "any" -> PGValue -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "any" -> PGValue -> PGValue #

PGParameter "bigint" Int64 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bigint" -> Int64 -> PGTextValue #

pgLiteral :: PGTypeID "bigint" -> Int64 -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bigint" -> Int64 -> PGValue #

PGParameter "boolean" Bool 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "boolean" -> Bool -> PGTextValue #

pgLiteral :: PGTypeID "boolean" -> Bool -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "boolean" -> Bool -> PGValue #

PGParameter "bytea" ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bytea" -> ByteString -> PGTextValue #

pgLiteral :: PGTypeID "bytea" -> ByteString -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bytea" -> ByteString -> PGValue #

PGParameter "bytea" ByteString 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "bytea" -> ByteString -> PGTextValue #

pgLiteral :: PGTypeID "bytea" -> ByteString -> ByteString0 #

pgEncodeValue :: PGTypeEnv -> PGTypeID "bytea" -> ByteString -> PGValue #

PGParameter "date" Day 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "date" -> Day -> PGTextValue #

pgLiteral :: PGTypeID "date" -> Day -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "date" -> Day -> PGValue #

PGParameter "double precision" Double 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "double precision" -> Double -> PGTextValue #

pgLiteral :: PGTypeID "double precision" -> Double -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "double precision" -> Double -> PGValue #

PGParameter "double precision" Float 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "double precision" -> Float -> PGTextValue #

pgLiteral :: PGTypeID "double precision" -> Float -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "double precision" -> Float -> PGValue #

PGParameter "integer" Int32 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "integer" -> Int32 -> PGTextValue #

pgLiteral :: PGTypeID "integer" -> Int32 -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "integer" -> Int32 -> PGValue #

PGParameter "interval" DiffTime 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "interval" -> DiffTime -> PGTextValue #

pgLiteral :: PGTypeID "interval" -> DiffTime -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "interval" -> DiffTime -> PGValue #

PGParameter "json" Value 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "json" -> Value -> PGTextValue #

pgLiteral :: PGTypeID "json" -> Value -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "json" -> Value -> PGValue #

PGParameter "jsonb" Value 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "jsonb" -> Value -> PGTextValue #

pgLiteral :: PGTypeID "jsonb" -> Value -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "jsonb" -> Value -> PGValue #

PGParameter "numeric" Rational 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "numeric" -> Rational -> PGTextValue #

pgLiteral :: PGTypeID "numeric" -> Rational -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "numeric" -> Rational -> PGValue #

PGParameter "numeric" Scientific 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "numeric" -> Scientific -> PGTextValue #

pgLiteral :: PGTypeID "numeric" -> Scientific -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "numeric" -> Scientific -> PGValue #

PGParameter "oid" OID 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "oid" -> OID -> PGTextValue #

pgLiteral :: PGTypeID "oid" -> OID -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "oid" -> OID -> PGValue #

PGParameter "real" Float 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "real" -> Float -> PGTextValue #

pgLiteral :: PGTypeID "real" -> Float -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "real" -> Float -> PGValue #

PGParameter "smallint" Int16 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "smallint" -> Int16 -> PGTextValue #

pgLiteral :: PGTypeID "smallint" -> Int16 -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "smallint" -> Int16 -> PGValue #

PGParameter "time without time zone" TimeOfDay 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "time without time zone" -> TimeOfDay -> PGTextValue #

pgLiteral :: PGTypeID "time without time zone" -> TimeOfDay -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "time without time zone" -> TimeOfDay -> PGValue #

PGParameter "timestamp with time zone" UTCTime 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "timestamp with time zone" -> UTCTime -> PGTextValue #

pgLiteral :: PGTypeID "timestamp with time zone" -> UTCTime -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "timestamp with time zone" -> UTCTime -> PGValue #

PGParameter "timestamp without time zone" LocalTime 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "timestamp without time zone" -> LocalTime -> PGTextValue #

pgLiteral :: PGTypeID "timestamp without time zone" -> LocalTime -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "timestamp without time zone" -> LocalTime -> PGValue #

PGParameter "uuid" UUID 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "uuid" -> UUID -> PGTextValue #

pgLiteral :: PGTypeID "uuid" -> UUID -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "uuid" -> UUID -> PGValue #

PGParameter "void" () 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "void" -> () -> PGTextValue #

pgLiteral :: PGTypeID "void" -> () -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "void" -> () -> PGValue #

PGParameter t a => PGParameter t (Maybe a) 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID t -> Maybe a -> PGTextValue #

pgLiteral :: PGTypeID t -> Maybe a -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID t -> Maybe a -> PGValue #

PGParameter "time with time zone" (TimeOfDay, TimeZone) 
Instance details

Defined in Database.PostgreSQL.Typed.Types

Methods

pgEncode :: PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> PGTextValue #

pgLiteral :: PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> ByteString #

pgEncodeValue :: PGTypeEnv -> PGTypeID "time with time zone" -> (TimeOfDay, TimeZone) -> PGValue #

Orphan instances

PGType "jsonb" => PGArrayType "jsonb[]" Source # 
Instance details

Associated Types

type PGElemType "jsonb[]" :: Symbol #

Methods

pgArrayElementType :: PGTypeID "jsonb[]" -> PGTypeID (PGElemType "jsonb[]") #

pgArrayDelim :: PGTypeID "jsonb[]" -> Char #

PGType "jsonb" => PGType "jsonb[]" Source # 
Instance details

Associated Types

type PGVal "jsonb[]" #

Methods

pgTypeName :: PGTypeID "jsonb[]" -> PGName #

pgBinaryColumn :: PGTypeEnv -> PGTypeID "jsonb[]" -> Bool #