hpqtypes-1.6.1.0: Haskell bindings to libpqtypes

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.PQTypes.ToSQL

Synopsis

Documentation

newtype ParamAllocator Source #

alloca-like producer of PGparam objects.

Constructors

ParamAllocator (forall r. (Ptr PGparam -> IO r) -> IO r) 

class PQFormat t => ToSQL t where Source #

Class which represents "from Haskell type to SQL (libpqtypes) type" transformation.

Associated Types

type PQDest t :: * Source #

Destination type (used by libpqtypes).

Methods

toSQL Source #

Arguments

:: t

Value to be put.

-> ParamAllocator

PGparam allocator.

-> (Ptr (PQDest t) -> IO r)

Continuation that puts converted value into inner PGparam.

-> IO r 

Put supplied value into inner PGparam.

Instances
ToSQL Bool Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Bool :: Type Source #

Methods

toSQL :: Bool -> ParamAllocator -> (Ptr (PQDest Bool) -> IO r) -> IO r Source #

ToSQL Char Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Char :: Type Source #

Methods

toSQL :: Char -> ParamAllocator -> (Ptr (PQDest Char) -> IO r) -> IO r Source #

ToSQL Double Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Double :: Type Source #

Methods

toSQL :: Double -> ParamAllocator -> (Ptr (PQDest Double) -> IO r) -> IO r Source #

ToSQL Float Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Float :: Type Source #

Methods

toSQL :: Float -> ParamAllocator -> (Ptr (PQDest Float) -> IO r) -> IO r Source #

ToSQL Int Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Int :: Type Source #

Methods

toSQL :: Int -> ParamAllocator -> (Ptr (PQDest Int) -> IO r) -> IO r Source #

ToSQL Int16 Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Int16 :: Type Source #

Methods

toSQL :: Int16 -> ParamAllocator -> (Ptr (PQDest Int16) -> IO r) -> IO r Source #

ToSQL Int32 Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Int32 :: Type Source #

Methods

toSQL :: Int32 -> ParamAllocator -> (Ptr (PQDest Int32) -> IO r) -> IO r Source #

ToSQL Int64 Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Int64 :: Type Source #

Methods

toSQL :: Int64 -> ParamAllocator -> (Ptr (PQDest Int64) -> IO r) -> IO r Source #

ToSQL Word8 Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Word8 :: Type Source #

Methods

toSQL :: Word8 -> ParamAllocator -> (Ptr (PQDest Word8) -> IO r) -> IO r Source #

ToSQL ByteString Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest ByteString :: Type Source #

ToSQL ByteString Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest ByteString :: Type Source #

ToSQL Text Source #

Encodes underlying C string as UTF-8, so if you are working with a different encoding, you should not rely on this instance.

Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Text :: Type Source #

Methods

toSQL :: Text -> ParamAllocator -> (Ptr (PQDest Text) -> IO r) -> IO r Source #

ToSQL UTCTime Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest UTCTime :: Type Source #

Methods

toSQL :: UTCTime -> ParamAllocator -> (Ptr (PQDest UTCTime) -> IO r) -> IO r Source #

ToSQL Text Source #

Encodes underlying C string as UTF-8, so if you are working with a different encoding, you should not rely on this instance.

Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Text :: Type Source #

Methods

toSQL :: Text -> ParamAllocator -> (Ptr (PQDest Text) -> IO r) -> IO r Source #

ToSQL String Source #

Encodes underlying C string as UTF-8, so if you are working with a different encoding, you should not rely on this instance.

Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest String :: Type Source #

Methods

toSQL :: String -> ParamAllocator -> (Ptr (PQDest String) -> IO r) -> IO r Source #

ToSQL ZonedTime Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest ZonedTime :: Type Source #

Methods

toSQL :: ZonedTime -> ParamAllocator -> (Ptr (PQDest ZonedTime) -> IO r) -> IO r Source #

ToSQL LocalTime Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest LocalTime :: Type Source #

Methods

toSQL :: LocalTime -> ParamAllocator -> (Ptr (PQDest LocalTime) -> IO r) -> IO r Source #

ToSQL TimeOfDay Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest TimeOfDay :: Type Source #

Methods

toSQL :: TimeOfDay -> ParamAllocator -> (Ptr (PQDest TimeOfDay) -> IO r) -> IO r Source #

ToSQL Day Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest Day :: Type Source #

Methods

toSQL :: Day -> ParamAllocator -> (Ptr (PQDest Day) -> IO r) -> IO r Source #

ToSQL Interval Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Interval

Associated Types

type PQDest Interval :: Type Source #

Methods

toSQL :: Interval -> ParamAllocator -> (Ptr (PQDest Interval) -> IO r) -> IO r Source #

ToSQL XML Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.XML

Associated Types

type PQDest XML :: Type Source #

Methods

toSQL :: XML -> ParamAllocator -> (Ptr (PQDest XML) -> IO r) -> IO r Source #

ToSQL t => ToSQL (Maybe t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.ToSQL

Associated Types

type PQDest (Maybe t) :: Type Source #

Methods

toSQL :: Maybe t -> ParamAllocator -> (Ptr (PQDest (Maybe t)) -> IO r) -> IO r Source #

ToSQL (JSONB ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSONB ByteString) :: Type Source #

ToSQL (JSONB ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSONB ByteString) :: Type Source #

ToSQL (JSONB Value) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSONB Value) :: Type Source #

Methods

toSQL :: JSONB Value -> ParamAllocator -> (Ptr (PQDest (JSONB Value)) -> IO r) -> IO r Source #

ToSQL (JSON ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSON ByteString) :: Type Source #

ToSQL (JSON ByteString) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSON ByteString) :: Type Source #

ToSQL (JSON Value) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.JSON

Associated Types

type PQDest (JSON Value) :: Type Source #

Methods

toSQL :: JSON Value -> ParamAllocator -> (Ptr (PQDest (JSON Value)) -> IO r) -> IO r Source #

CompositeToSQL t => ToSQL (Composite t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Composite

Associated Types

type PQDest (Composite t) :: Type Source #

Methods

toSQL :: Composite t -> ParamAllocator -> (Ptr (PQDest (Composite t)) -> IO r) -> IO r Source #

CompositeToSQL t => ToSQL (CompositeArray2 t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Array

Associated Types

type PQDest (CompositeArray2 t) :: Type Source #

ToSQL t => ToSQL (Array2 t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Array

Associated Types

type PQDest (Array2 t) :: Type Source #

Methods

toSQL :: Array2 t -> ParamAllocator -> (Ptr (PQDest (Array2 t)) -> IO r) -> IO r Source #

CompositeToSQL t => ToSQL (CompositeArray1 t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Array

Associated Types

type PQDest (CompositeArray1 t) :: Type Source #

ToSQL t => ToSQL (Array1 t) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.Array

Associated Types

type PQDest (Array1 t) :: Type Source #

Methods

toSQL :: Array1 t -> ParamAllocator -> (Ptr (PQDest (Array1 t)) -> IO r) -> IO r Source #

putAsPtr :: Storable t => t -> (Ptr t -> IO r) -> IO r Source #

Function that abstracts away common elements of most ToSQL instance definitions to make them easier to write and less verbose.