Copyright | 2015 Dylan Simon |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Database.PostgreSQL.Typed.Dynamic
Description
Automatic (dynamic) marshalling of PostgreSQL values based on Haskell types (not SQL statements). This is intended for direct construction of queries and query data, bypassing the normal SQL type inference.
Synopsis
- class (PGParameter (PGRepType a) a, PGColumn (PGRepType a) a) => PGRep a where
- pgTypeOf :: a -> PGTypeID (PGRepType a)
- pgTypeOfProxy :: Proxy a -> PGTypeID (PGRepType a)
- pgEncodeRep :: PGRep a => a -> PGValue
- pgDecodeRep :: forall a. PGRep a => PGValue -> a
- pgLiteralRep :: PGRep a => a -> ByteString
- pgLiteralString :: PGRep a => a -> String
- pgSafeLiteral :: PGRep a => a -> ByteString
- pgSafeLiteralString :: PGRep a => a -> String
- pgSubstituteLiterals :: String -> ExpQ
Documentation
class (PGParameter (PGRepType a) a, PGColumn (PGRepType a) a) => PGRep a Source #
Represents canonical/default PostgreSQL representation for various Haskell types, allowing convenient type-driven marshalling.
Associated Types
type PGRepType a :: Symbol Source #
The PostgreSOL type that this type should be converted to.
Instances
PGRep Int16 Source # | |
PGRep Int32 Source # | |
PGRep Int64 Source # | |
PGRep Rational Source # | |
PGRep ByteString Source # | |
Defined in Database.PostgreSQL.Typed.Dynamic Associated Types type PGRepType ByteString :: Symbol Source # | |
PGRep OID Source # | |
PGRep PGName Source # | |
PGRep Scientific Source # | |
Defined in Database.PostgreSQL.Typed.Dynamic Associated Types type PGRepType Scientific :: Symbol Source # | |
PGRep Text Source # | |
PGRep Day Source # | |
PGRep DiffTime Source # | |
PGRep UTCTime Source # | |
PGRep LocalTime Source # | |
PGRep TimeOfDay Source # | |
PGRep UUID Source # | |
PGRep String Source # | |
PGRep () Source # | |
Defined in Database.PostgreSQL.Typed.Dynamic | |
PGRep Bool Source # | |
PGRep Char Source # | |
PGRep Double Source # | |
PGRep Float Source # | |
PGRep a => PGRep (Maybe a) Source # | |
PGRep (TimeOfDay, TimeZone) Source # | |
pgEncodeRep :: PGRep a => a -> PGValue Source #
Encode a value using pgEncodeValue
.
pgDecodeRep :: forall a. PGRep a => PGValue -> a Source #
Decode a value using pgDecodeValue
.
pgLiteralRep :: PGRep a => a -> ByteString Source #
Produce a literal value for interpolation in a SQL statement using pgLiteral
. Using pgSafeLiteral
is usually safer as it includes type cast.
pgLiteralString :: PGRep a => a -> String Source #
Produce a raw SQL literal from a value. Using pgSafeLiteral
is usually safer when interpolating in a SQL statement.
pgSafeLiteral :: PGRep a => a -> ByteString Source #
Produce a safely type-cast literal value for interpolation in a SQL statement, e.g., "'123'::integer".
pgSafeLiteralString :: PGRep a => a -> String Source #
Identical to
but more efficient.unpack
. pgSafeLiteral
pgSubstituteLiterals :: String -> ExpQ Source #
Create an expression that literally substitutes each instance of ${expr}
for the result of pgSafeLiteral expr
, producing a lazy ByteString
.
This lets you do safe, type-driven literal substitution into SQL fragments without needing a full query, bypassing placeholder inference and any prepared queries, for example when using pgSimpleQuery
or pgSimpleQueries_
.
Unlike most other TH functions, this does not require any database connection.