psql-0.0.0: PostgreSQL client
Safe HaskellNone
LanguageHaskell2010

PostgreSQL.Param

Contents

Description

Here are things dealing with query parameters.

Synopsis

Basics

data Type Source #

Parameter type

Since: 0.0.0

Constructors

InferredType

Type is inferred on the server side

Since: 0.0.0

StaticType Oid

Explicit static type

Since: 0.0.0

Instances

Instances details
Eq Type Source # 
Instance details

Defined in PostgreSQL.Param

Methods

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

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

Ord Type Source # 
Instance details

Defined in PostgreSQL.Param

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in PostgreSQL.Param

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

typeOid :: Type -> Oid Source #

Get the OID for the type.

Since: 0.0.0

data Info a Source #

Static parameter information

Since: 0.0.0

Constructors

Info 

Fields

Instances

Instances details
Functor Info Source # 
Instance details

Defined in PostgreSQL.Param

Methods

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

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

Foldable Info Source # 
Instance details

Defined in PostgreSQL.Param

Methods

fold :: Monoid m => Info m -> m #

foldMap :: Monoid m => (a -> m) -> Info a -> m #

foldMap' :: Monoid m => (a -> m) -> Info a -> m #

foldr :: (a -> b -> b) -> b -> Info a -> b #

foldr' :: (a -> b -> b) -> b -> Info a -> b #

foldl :: (b -> a -> b) -> b -> Info a -> b #

foldl' :: (b -> a -> b) -> b -> Info a -> b #

foldr1 :: (a -> a -> a) -> Info a -> a #

foldl1 :: (a -> a -> a) -> Info a -> a #

toList :: Info a -> [a] #

null :: Info a -> Bool #

length :: Info a -> Int #

elem :: Eq a => a -> Info a -> Bool #

maximum :: Ord a => Info a -> a #

minimum :: Ord a => Info a -> a #

sum :: Num a => Info a -> a #

product :: Num a => Info a -> a #

Traversable Info Source # 
Instance details

Defined in PostgreSQL.Param

Methods

traverse :: Applicative f => (a -> f b) -> Info a -> f (Info b) #

sequenceA :: Applicative f => Info (f a) -> f (Info a) #

mapM :: Monad m => (a -> m b) -> Info a -> m (Info b) #

sequence :: Monad m => Info (m a) -> m (Info a) #

Generic (Info a) Source # 
Instance details

Defined in PostgreSQL.Param

Associated Types

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

Methods

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

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

type Rep (Info a) Source # 
Instance details

Defined in PostgreSQL.Param

type Rep (Info a) = D1 ('MetaData "Info" "PostgreSQL.Param" "psql-0.0.0-inplace" 'False) (C1 ('MetaCons "Info" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Just "info_typeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "info_format") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Format) :*: S1 ('MetaSel ('Just "info_pack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

data Value Source #

Value

Since: 0.0.0

Constructors

Null 
Value ByteString 

Instances

Instances details
Eq Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

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

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

Ord Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

compare :: Value -> Value -> Ordering #

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

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

(>) :: Value -> Value -> Bool #

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

Methods

fromString :: String -> Value #

Param Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Value -> Value) Source #

data Oid #

Instances

Instances details
Eq Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

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

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

Ord Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

compare :: Oid -> Oid -> Ordering #

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

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

(>) :: Oid -> Oid -> Bool #

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

max :: Oid -> Oid -> Oid #

min :: Oid -> Oid -> Oid #

Read Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

showsPrec :: Int -> Oid -> ShowS #

show :: Oid -> String #

showList :: [Oid] -> ShowS #

Storable Oid 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

sizeOf :: Oid -> Int #

alignment :: Oid -> Int #

peekElemOff :: Ptr Oid -> Int -> IO Oid #

pokeElemOff :: Ptr Oid -> Int -> Oid -> IO () #

peekByteOff :: Ptr b -> Int -> IO Oid #

pokeByteOff :: Ptr b -> Int -> Oid -> IO () #

peek :: Ptr Oid -> IO Oid #

poke :: Ptr Oid -> Oid -> IO () #

AutoColumn Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Result.Column

Param Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Oid -> Value) Source #

data Format #

Constructors

Text 
Binary 

Instances

Instances details
Enum Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Eq Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Methods

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

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

Ord Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

Show Format 
Instance details

Defined in Database.PostgreSQL.LibPQ

newtype PackedParam Source #

Packed parameter

Since: 0.0.0

Constructors

PackedParam (Maybe (Oid, ByteString, Format)) 

Instances

Instances details
Show PackedParam Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

packParam :: Info Value -> PackedParam Source #

Pack a parameter into a postgresql-libpq format.

Since: 0.0.0

toPrepared :: PackedParam -> PackedParamPrepared Source #

Convert PackedParam.

Since: 0.0.0

newtype PackedParamPrepared Source #

Packed parameter for a prepared query

Since: 0.0.0

Instances

Instances details
Show PackedParamPrepared Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Types

packParamPrepared :: Info Value -> PackedParamPrepared Source #

Pack a parameter for a prepared query into a postgresql-libpq format.

Since: 0.0.0

Class

class Param a where Source #

a can be used as a parameter

Since: 0.0.0

Methods

paramInfo :: Info (a -> Value) Source #

Parameter information

Since: 0.0.0

Instances

Instances details
Param Double Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Param Integer Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Param Text Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Text -> Value) Source #

Param Oid Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Oid -> Value) Source #

Param RegType Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Param Value Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

Methods

paramInfo :: Info (Value -> Value) Source #

Param RawText Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param

newtype RawText Source #

Raw textual parameter

Since: 0.0.0

Constructors

RawText 

Instances

Instances details
Eq RawText Source # 
Instance details

Defined in PostgreSQL.Param

Methods

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

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

Ord RawText Source # 
Instance details

Defined in PostgreSQL.Param

Show RawText Source # 
Instance details

Defined in PostgreSQL.Param

Param RawText Source #

Since: 0.0.0

Instance details

Defined in PostgreSQL.Param