| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Session.Encode
Description
encoding of statement parameters
Synopsis
- newtype EncodeParams (db :: SchemasType) (tys :: [k]) (x :: Type) = EncodeParams {
- runEncodeParams :: x -> ReaderT (K Connection db) IO (NP (K (Maybe Encoding)) tys)
- class (IsProductType x xs, params ~ TuplePG x, All (OidOfNull db) params, AllZip (ToParam db) params xs) => GenericParams db params x xs where
- genericParams :: EncodeParams db params x
- nilParams :: EncodeParams db '[] x
- (.*) :: forall db x0 ty x tys. (ToParam db ty x0, ty ~ NullPG x0) => (x -> x0) -> EncodeParams db tys x -> EncodeParams db (ty ': tys) x
- (*.) :: forall db x x0 ty0 x1 ty1. (ToParam db ty0 x0, ty0 ~ NullPG x0, ToParam db ty1 x1, ty1 ~ NullPG x1) => (x -> x0) -> (x -> x1) -> EncodeParams db '[ty0, ty1] x
- aParam :: forall db x ty. (ToParam db ty x, ty ~ NullPG x) => EncodeParams db '[ty] x
- appendParams :: EncodeParams db params0 x -> EncodeParams db params1 x -> EncodeParams db (Join params0 params1) x
- enumParam :: (PG x ~ 'PGenum labels, All KnownSymbol labels) => (x -> NS PGlabel labels) -> x -> ReaderT (K Connection db) IO Encoding
- rowParam :: (PG x ~ 'PGcomposite row, All (OidOfField db) row) => EncodeParams db row x -> x -> ReaderT (K Connection db) IO Encoding
- genericRowParams :: forall db row x xs. (IsRecord x xs, AllZip (ToField db) row xs) => EncodeParams db row x
- (.#) :: forall db x0 fld ty x tys. (ToParam db ty x0, ty ~ NullPG x0) => Aliased ((->) x) (fld ::: x0) -> EncodeParams db tys x -> EncodeParams db ((fld ::: ty) ': tys) x
- (#.) :: forall db x x0 fld0 ty0 x1 fld1 ty1. (ToParam db ty0 x0, ty0 ~ NullPG x0, ToParam db ty1 x1, ty1 ~ NullPG x1) => Aliased ((->) x) (fld0 ::: x0) -> Aliased ((->) x) (fld1 ::: x1) -> EncodeParams db '[fld0 ::: ty0, fld1 ::: ty1] 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 :: [k]) (x :: Type) Source #
EncodeParams describes an encoding of a Haskell Type
into a list of parameter NullTypes or into a RowType.
>>>conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb user=postgres password=postgres">>>:{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
>>>:{let encode :: EncodeParams '[] '["fst" ::: 'NotNull 'PGint2, "snd" ::: 'NotNull ('PGchar 1)] (Int16, Char) encode = fst `as` #fst #. snd `as` #snd in runReaderT (runEncodeParams encode (1,'a')) conn :} K (Just "\NUL\SOH") :* K (Just "a") :* Nil
>>>finish conn
Constructors
| EncodeParams | |
Fields
| |
Instances
| (ToParam db ty x, ty ~ NullPG x) => IsLabel fld (EncodeParams db '[fld ::: ty] x) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode Methods fromLabel :: EncodeParams db '[fld ::: ty] x # | |
| 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 # | |
class (IsProductType x xs, params ~ TuplePG x, All (OidOfNull db) params, AllZip (ToParam db) params xs) => GenericParams db params x xs where Source #
A GenericParams constraint to ensure that a Haskell type
is a product type,
has a TuplePG,
and all its terms have known Oids,
and can be encoded to corresponding Postgres types.
Methods
genericParams :: 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 user=postgres password=postgres">>>:{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
Instances
| (params ~ TuplePG x, All (OidOfNull db) params, IsProductType x xs, AllZip (ToParam db) params xs) => GenericParams db params x xs Source # | |
Defined in Squeal.PostgreSQL.Session.Encode Methods genericParams :: EncodeParams db params x Source # | |
nilParams :: EncodeParams db '[] x Source #
Encode 0 parameters.
Arguments
| :: forall db x0 ty x tys. (ToParam db ty x0, ty ~ NullPG 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 user=postgres password=postgres">>>:{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
| :: forall db x x0 ty0 x1 ty1. (ToParam db ty0 x0, ty0 ~ NullPG x0, ToParam db ty1 x1, ty1 ~ NullPG 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 user=postgres password=postgres">>>:{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
Arguments
| :: forall db x ty. (ToParam db ty x, ty ~ NullPG x) | |
| => EncodeParams db '[ty] x | a single parameter |
Encode 1 parameter.
>>>conn <- connectdb @'[] "host=localhost port=5432 dbname=exampledb user=postgres password=postgres">>>:{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 user=postgres password=postgres">>>:{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
Arguments
| :: (PG x ~ 'PGenum labels, All KnownSymbol labels) | |
| => (x -> NS PGlabel labels) | match cases with enum |
| -> x -> ReaderT (K Connection db) IO Encoding |
>>>:set -XLambdaCase -XFlexibleInstances>>>:{data Dir = North | South | East | West instance IsPG Dir where type PG Dir = 'PGenum '["north", "south", "east", "west"] instance ToPG db Dir where toPG = enumParam $ \case North -> label @"north" South -> label @"south" East -> label @"east" West -> label @"west" :}
Arguments
| :: (PG x ~ 'PGcomposite row, All (OidOfField db) row) | |
| => EncodeParams db row x | |
| -> x -> ReaderT (K Connection db) IO Encoding |
>>>:set -XTypeFamilies -XFlexibleInstances>>>:{data Complex = Complex { real :: Double , imaginary :: Double } instance IsPG Complex where type PG Complex = 'PGcomposite '[ "re" ::: 'NotNull 'PGfloat8, "im" ::: 'NotNull 'PGfloat8] instance ToPG db Complex where toPG = rowParam $ real `as` #re #. imaginary `as` #im :}
genericRowParams :: forall db row x xs. (IsRecord x xs, AllZip (ToField db) row xs) => EncodeParams db row x Source #
>>>import GHC.Generics as GHC>>>:{data L = L {frst :: Int16, scnd :: Char} deriving stock (GHC.Generic, Show) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) data R = R {thrd :: Bool, frth :: Bool} deriving stock (GHC.Generic, Show) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) instance IsPG (L,R) where type PG (L,R) = 'PGcomposite '[ "frst" ::: 'NotNull 'PGint2, "scnd" ::: 'NotNull ('PGchar 1), "thrd" ::: 'NotNull 'PGbool, "frth" ::: 'NotNull 'PGbool] instance ToPG db (L,R) where toPG = rowParam $ contramap fst genericRowParams `appendParams` contramap snd genericRowParams :}
Arguments
| :: forall db x0 fld ty x tys. (ToParam db ty x0, ty ~ NullPG x0) | |
| => Aliased ((->) x) (fld ::: x0) | head |
| -> EncodeParams db tys x | tail |
| -> EncodeParams db ((fld ::: ty) ': tys) x |
Cons a row parameter encoding for rowParam.
Arguments
| :: forall db x x0 fld0 ty0 x1 fld1 ty1. (ToParam db ty0 x0, ty0 ~ NullPG x0, ToParam db ty1 x1, ty1 ~ NullPG x1) | |
| => Aliased ((->) x) (fld0 ::: x0) | second to last |
| -> Aliased ((->) x) (fld1 ::: x1) | last |
| -> EncodeParams db '[fld0 ::: ty0, fld1 ::: ty1] x |
End a row parameter encoding for rowParam.
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 user=postgres password=postgres">>>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 | |