squeal-postgresql-0.6.0.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Session.Encode

Contents

Description

encoding of statement parameters

Synopsis

Encode Parameters

newtype EncodeParams (db :: SchemasType) (tys :: [NullType]) (x :: Type) Source #

EncodeParams describes an encoding of a Haskell Type into a list of parameter NullTypes.

>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[]
    '[ 'NotNull 'PGint2, 'NotNull ('PGchar 1), 'NotNull 'PGtext]
    (Int16, (Char, String))
  encode = fst .* fst.snd *. snd.snd
in runReaderT (runEncodeParams encode (1,('a',"foo"))) conn
:}
K (Just "\NUL\SOH") :* K (Just "a") :* K (Just "foo") :* Nil
>>> finish conn

Constructors

EncodeParams 

Fields

Instances
Contravariant (EncodeParams db tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Methods

contramap :: (a -> b) -> EncodeParams db tys b -> EncodeParams db tys a #

(>$) :: b -> EncodeParams db tys b -> EncodeParams db tys a #

genericParams :: forall db params x xs. (IsProductType x xs, AllZip (ToParam db) params xs) => EncodeParams db params x Source #

Parameter encoding for Generic tuples and records.

>>> import qualified GHC.Generics as GHC
>>> import qualified Generics.SOP as SOP
>>> data Two = Two Int16 String deriving (GHC.Generic, SOP.Generic)
>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[] '[ 'NotNull 'PGint2, 'NotNull 'PGtext] Two
  encode = genericParams
in runReaderT (runEncodeParams encode (Two 2 "two")) conn
:}
K (Just "\NUL\STX") :* K (Just "two") :* Nil
>>> :{
let
  encode :: EncodeParams '[] '[ 'NotNull 'PGint2, 'NotNull 'PGtext] (Int16, String)
  encode = genericParams
in runReaderT (runEncodeParams encode (2, "two")) conn
:}
K (Just "\NUL\STX") :* K (Just "two") :* Nil
>>> finish conn

nilParams :: EncodeParams db '[] x Source #

Encode 0 parameters.

(.*) infixr 5 Source #

Arguments

:: ToParam db ty x0 
=> (x -> x0)

head

-> EncodeParams db tys x

tail

-> EncodeParams db (ty ': tys) x 

Cons a parameter encoding.

>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[]
    '[ 'Null 'PGint4, 'NotNull 'PGtext]
    (Maybe Int32, String)
  encode = fst .* snd .* nilParams
in runReaderT (runEncodeParams encode (Nothing, "foo")) conn
:}
K Nothing :* K (Just "foo") :* Nil
>>> finish conn

(*.) infixl 8 Source #

Arguments

:: (ToParam db ty0 x0, ToParam db ty1 x1) 
=> (x -> x0)

second to last

-> (x -> x1)

last

-> EncodeParams db '[ty0, ty1] x 

End a parameter encoding.

>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[]
    '[ 'Null 'PGint4, 'NotNull 'PGtext, 'NotNull ('PGchar 1)]
    (Maybe Int32, String, Char)
  encode = (\(x,_,_) -> x) .* (\(_,y,_) -> y) *. (\(_,_,z) -> z)
in runReaderT (runEncodeParams encode (Nothing, "foo", 'z')) conn
:}
K Nothing :* K (Just "foo") :* K (Just "z") :* Nil
>>> finish conn

aParam :: forall db x. ToParam db (NullPG x) x => EncodeParams db '[NullPG x] x Source #

Encode 1 parameter.

>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[] '[ 'NotNull 'PGint4] Int32
  encode = aParam
in runReaderT (runEncodeParams encode 1776) conn
:}
K (Just "\NUL\NUL\ACK\240") :* Nil
>>> finish conn

appendParams Source #

Arguments

:: EncodeParams db params0 x

left

-> EncodeParams db params1 x

right

-> EncodeParams db (Join params0 params1) x 

Append parameter encodings.

>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> :{
let
  encode :: EncodeParams '[]
    '[ 'NotNull 'PGint4, 'NotNull 'PGint2]
    (Int32, Int16)
  encode = contramap fst aParam `appendParams` contramap snd aParam
in runReaderT (runEncodeParams encode (1776, 2)) conn
:}
K (Just "\NUL\NUL\ACK\240") :* K (Just "\NUL\STX") :* Nil
>>> finish conn

Encoding Classes

class IsPG x => ToPG (db :: SchemasType) (x :: Type) where Source #

A ToPG constraint gives an encoding of a Haskell Type into into the binary format of a PostgreSQL PGType.

Methods

toPG :: x -> ReaderT (K Connection db) IO Encoding Source #

>>> :set -XTypeApplications -XDataKinds
>>> conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb"
>>> runReaderT (toPG @'[] False) conn
"\NUL"
>>> runReaderT (toPG @'[] (0 :: Int16)) conn
"\NUL\NUL"
>>> runReaderT (toPG @'[] (0 :: Int32)) conn
"\NUL\NUL\NUL\NUL"
>>> :set -XMultiParamTypeClasses -XGeneralizedNewtypeDeriving
>>> newtype UserId = UserId { getUserId :: Int64 } deriving newtype (IsPG, ToPG db)
>>> runReaderT (toPG @'[] (UserId 0)) conn
"\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL"
>>> finish conn
Instances
ToPG db Value Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db DiffTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db UTCTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db LocalTime Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db TimeOfDay Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Day Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db ByteString Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db String Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Text Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Char Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db UUID Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Money Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Scientific Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Double Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Float Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Oid Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Int64 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Int32 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Int16 Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db Bool Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db x => ToPG db (Range x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(SListI fields, IsRecord x xs, AllZip (ToField db) fields xs, All (OidOfField db) fields, RowPG x ~ fields) => ToPG db (Composite x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(IsEnumType x, HasDatatypeInfo x, LabelsPG x ~ labels) => ToPG db (Enumerated x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(ToArray db dims ty x, OidOfNull db ty) => ToPG db (FixArray x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(NullPG x ~ ty, ToArray db ([] :: [Nat]) ty x, OidOfNull db ty) => ToPG db (VarArray (Vector x)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(NullPG x ~ ty, ToArray db ([] :: [Nat]) ty x, OidOfNull db ty) => ToPG db (VarArray [x]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToJSON x => ToPG db (Jsonb x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToJSON x => ToPG db (Json x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db (NetAddr IP) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

ToPG db (TimeOfDay, TimeZone) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

class ToParam (db :: SchemasType) (ty :: NullType) (x :: Type) where Source #

A ToParam constraint gives an encoding of a Haskell Type into into the binary format of a PostgreSQL NullType. You should not define instances for ToParam, just use the provided instances.

Instances
(ToPG db x, pg ~ PG x) => ToParam db (NotNull pg) x Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(ToPG db x, pg ~ PG x) => ToParam db (Null pg) (Maybe x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

class ToField (db :: SchemasType) (field :: (Symbol, NullType)) (x :: (Symbol, Type)) where Source #

A ToField constraint lifts the ToPG parser to an encoding of a (Symbol, Type) to a (Symbol, NullityType), encoding Nulls to Maybes. You should not define instances for ToField, just use the provided instances.

Methods

toField :: P x -> ReaderT (K Connection db) IO (K (Maybe Encoding) field) Source #

Instances
(fld0 ~ fld1, ToParam db ty x) => ToField db (fld0 ::: ty) (fld1 ::: x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Methods

toField :: P (fld1 ::: x) -> ReaderT (K Connection db) IO (K (Maybe Encoding) (fld0 ::: ty)) Source #

class ToArray (db :: SchemasType) (dims :: [Nat]) (ty :: NullType) (x :: Type) where Source #

A ToArray constraint gives an encoding of a Haskell Type into the binary format of a PostgreSQL fixed-length array. You should not define instances for ToArray, just use the provided instances.

Instances
(ToPG db x, pg ~ PG x) => ToArray db ([] :: [Nat]) (NotNull pg) x Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(ToPG db x, pg ~ PG x) => ToArray db ([] :: [Nat]) (Null pg) (Maybe x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

(IsProductType tuple xs, Length xs ~ dim, All (Type ~ x) xs, ToArray db dims ty x, KnownNat dim) => ToArray db (dim ': dims) ty tuple Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode