Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Session.Encode
Description
encoding of statement parameters
Synopsis
- newtype EncodeParams (db :: SchemasType) (tys :: [NullType]) (x :: Type) = EncodeParams {
- runEncodeParams :: x -> ReaderT (K Connection db) IO (NP (K (Maybe Encoding)) tys)
- genericParams :: forall db params x xs. (IsProductType x xs, AllZip (ToParam db) params xs) => EncodeParams db params x
- nilParams :: EncodeParams db '[] x
- (.*) :: forall db x0 ty x tys. ToParam db ty x0 => (x -> x0) -> EncodeParams db tys x -> EncodeParams db (ty ': tys) x
- (*.) :: forall db x x0 ty0 x1 ty1. (ToParam db ty0 x0, ToParam db ty1 x1) => (x -> x0) -> (x -> x1) -> EncodeParams db '[ty0, ty1] x
- aParam :: forall db x. ToParam db (NullPG x) x => EncodeParams db '[NullPG x] x
- appendParams :: EncodeParams db params0 x -> EncodeParams db params1 x -> EncodeParams db (Join params0 params1) x
- class IsPG x => ToPG (db :: SchemasType) (x :: Type) where
- class ToParam (db :: SchemasType) (ty :: NullType) (x :: Type) where
- class ToField (db :: SchemasType) (field :: (Symbol, NullType)) (x :: (Symbol, Type)) where
- class ToArray (db :: SchemasType) (dims :: [Nat]) (ty :: NullType) (x :: Type) where
- arrayPayload :: x -> ReaderT (K Connection db) IO Encoding
- arrayDims :: [Int32]
- arrayNulls :: Bool
Encode Parameters
newtype EncodeParams (db :: SchemasType) (tys :: [NullType]) (x :: Type) Source #
EncodeParams
describes an encoding of a Haskell Type
into a list of parameter NullType
s.
>>>
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 # | |
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.
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
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
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
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.
class ToField (db :: SchemasType) (field :: (Symbol, NullType)) (x :: (Symbol, Type)) where 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.
Methods
arrayPayload :: x -> ReaderT (K Connection db) IO Encoding Source #
arrayNulls :: Bool Source #
Instances
(ToPG db x, pg ~ PG x) => ToArray db ([] :: [Nat]) (NotNull pg) x Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
(ToPG db x, pg ~ PG x) => ToArray db ([] :: [Nat]) (Null pg) (Maybe x) Source # | |
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 # | |
Defined in Squeal.PostgreSQL.Session.Encode |