Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Binary
Description
This module provides binary encoding and decoding between Haskell and PostgreSQL types.
Instances are governed by the Generic
and HasDatatypeInfo
typeclasses, so you absolutely
do not need to define your own instances to decode retrieved rows into Haskell values or
to encode Haskell values into statement parameters.
Let's see some examples. We'll need some imports
>>>
import Data.Int (Int16)
>>>
import Data.Text (Text)
>>>
import Control.Monad (void)
>>>
import Control.Monad.Base (liftBase)
>>>
import Squeal.PostgreSQL
Define a Haskell datatype Row
that will serve as both the input and output of a simple
round trip query.
>>>
data Row = Row { col1 :: Int16, col2 :: Text, col3 :: Maybe Bool } deriving (Eq, GHC.Generic)
>>>
instance Generic Row
>>>
instance HasDatatypeInfo Row
>>>
:{
let roundTrip :: Query '[] (TuplePG Row) (RowPG Row) roundTrip = values_ $ parameter @1 int2 `as` #col1 :* parameter @2 text `as` #col2 :* parameter @3 bool `as` #col3 :}
So long as we can encode the parameters and then decode the result of the query, the input and output should be equal.
>>>
let input = Row 2 "hi" (Just True)
>>>
:{
void . withConnection "host=localhost port=5432 dbname=exampledb" $ do result <- runQueryParams roundTrip input Just output <- firstRow result liftBase . print $ input == output :} True
In addition to being able to encode and decode basic Haskell types
like Int16
and Text
, Squeal permits you to encode and decode Haskell types to
Postgres array, enumerated and composite types and json. Let's see another example,
this time using the Vector
type which corresponds to variable length arrays
and homogeneous tuples which correspond to fixed length arrays. We can even
create multi-dimensional fixed length arrays.
>>>
:{
data Row = Row { col1 :: Vector Int16 , col2 :: (Maybe Int16,Maybe Int16) , col3 :: ((Int16,Int16),(Int16,Int16),(Int16,Int16)) } deriving (Eq, GHC.Generic) :}
>>>
instance Generic Row
>>>
instance HasDatatypeInfo Row
Once again, we define a simple round trip query.
>>>
:{
let roundTrip :: Query '[] (TuplePG Row) (RowPG Row) roundTrip = values_ $ parameter @1 (int2 & vararray) `as` #col1 :* parameter @2 (int2 & fixarray @2) `as` #col2 :* parameter @3 (int2 & fixarray @2 & fixarray @3) `as` #col3 :}
>>>
:set -XOverloadedLists
>>>
let input = Row [1,2] (Just 1,Nothing) ((1,2),(3,4),(5,6))
>>>
:{
void . withConnection "host=localhost port=5432 dbname=exampledb" $ do result <- runQueryParams roundTrip input Just output <- firstRow result liftBase . print $ input == output :} True
Enumerated (enum) types are data types that comprise a static, ordered set of values. They are equivalent to Haskell algebraic data types whose constructors are nullary. An example of an enum type might be the days of the week, or a set of status values for a piece of data.
>>>
data Schwarma = Beef | Lamb | Chicken deriving (Eq, Show, GHC.Generic)
>>>
instance Generic Schwarma
>>>
instance HasDatatypeInfo Schwarma
A composite type represents the structure of a row or record; it is essentially just a list of field names and their data types.
>>>
data Person = Person {name :: Text, age :: Int32} deriving (Eq, Show, GHC.Generic)
>>>
instance Generic Person
>>>
instance HasDatatypeInfo Person
>>>
instance Aeson.FromJSON Person
>>>
instance Aeson.ToJSON Person
We can create the equivalent Postgres types directly from their Haskell types.
>>>
:{
type Schema = '[ "schwarma" ::: 'Typedef (PG (Enumerated Schwarma)) , "person" ::: 'Typedef (PG (Composite Person)) ] :}
>>>
:{
let setup :: Definition '[] Schema setup = createTypeEnumFrom @Schwarma #schwarma >>> createTypeCompositeFrom @Person #person :}
Let's demonstrate how to associate our Haskell types Schwarma
and Person
with enumerated, composite or json types in Postgres. First create a Haskell
Row
type using the Enumerated
, Composite
and Json
newtypes as fields.
>>>
:{
data Row = Row { schwarma :: Enumerated Schwarma , person1 :: Composite Person , person2 :: Json Person } deriving (Eq, GHC.Generic) :}
>>>
instance Generic Row
>>>
instance HasDatatypeInfo Row
>>>
:{
let input = Row (Enumerated Chicken) (Composite (Person "Faisal" 24)) (Json (Person "Ahmad" 48)) :}
Once again, define a round trip query.
>>>
:{
let roundTrip :: Query Schema (TuplePG Row) (RowPG Row) roundTrip = values_ $ parameter @1 (typedef #schwarma) `as` #schwarma :* parameter @2 (typedef #person) `as` #person1 :* parameter @3 json `as` #person2 :}
Finally, we can drop our type definitions.
>>>
:{
let teardown :: Definition Schema '[] teardown = dropType #schwarma >>> dropType #person :}
Now let's run it.
>>>
:{
let session = do result <- runQueryParams roundTrip input Just output <- firstRow result liftBase . print $ input == output in void . withConnection "host=localhost port=5432 dbname=exampledb" $ define setup & pqThen session & pqThen (define teardown) :} True
Encoding
class ToParam (x :: Type) (pg :: PGType) where Source #
A ToParam
constraint gives an encoding of a Haskell Type
into
into the binary format of a PostgreSQL PGType
.
Minimal complete definition
Methods
toParam :: x -> K Encoding pg Source #
>>>
:set -XTypeApplications -XDataKinds
>>>
toParam @Bool @'PGbool False
K "\NUL"
>>>
toParam @Int16 @'PGint2 0
K "\NUL\NUL"
>>>
toParam @Int32 @'PGint4 0
K "\NUL\NUL\NUL\NUL"
>>>
:set -XMultiParamTypeClasses
>>>
newtype Id = Id { getId :: Int16 } deriving Show
>>>
instance ToParam Id 'PGint2 where toParam = toParam . getId
>>>
toParam @Id @'PGint2 (Id 1)
K "\NUL\SOH"
Instances
class SListI tys => ToParams (x :: Type) (tys :: [NullityType]) where Source #
A ToParams
constraint generically sequences the encodings of Type
s
of the fields of a tuple or record to a row of ColumnType
s. You should
not define instances of ToParams
. Instead define Generic
instances
which in turn provide ToParams
instances.
Minimal complete definition
Methods
toParams :: x -> NP (K (Maybe Encoding)) tys Source #
>>>
type Params = '[ 'NotNull 'PGbool, 'Null 'PGint2]
>>>
toParams @(Bool, Maybe Int16) @'[ 'NotNull 'PGbool, 'Null 'PGint2] (False, Just 0)
K (Just "\NUL") :* K (Just "\NUL\NUL") :* Nil
>>>
:set -XDeriveGeneric
>>>
data Tuple = Tuple { p1 :: Bool, p2 :: Maybe Int16} deriving GHC.Generic
>>>
instance Generic Tuple
>>>
toParams @Tuple @Params (Tuple False (Just 0))
K (Just "\NUL") :* K (Just "\NUL\NUL") :* Nil
Decoding
class FromValue (pg :: PGType) (y :: Type) where Source #
A FromValue
constraint gives a parser from the binary format of
a PostgreSQL PGType
into a Haskell Type
.
Minimal complete definition
Methods
>>>
newtype Id = Id { getId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 Id where fromValue = Id <$> fromValue @'PGint2
Instances
class SListI result => FromRow (result :: RowType) y where Source #
A FromRow
constraint generically sequences the parsings of the columns
of a RowType
into the fields of a record Type
provided they have
the same field names. You should not define instances of FromRow
.
Instead define Generic
and HasDatatypeInfo
instances which in turn
provide FromRow
instances.
Minimal complete definition
Methods
fromRow :: NP (K (Maybe ByteString)) result -> Either Text y Source #
>>>
:set -XOverloadedStrings
>>>
import Data.Text
>>>
newtype UserId = UserId { getUserId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 UserId where fromValue = UserId <$> fromValue @'PGint2
>>>
data UserRow = UserRow { userId :: UserId, userName :: Maybe Text } deriving (Show, GHC.Generic)
>>>
instance Generic UserRow
>>>
instance HasDatatypeInfo UserRow
>>>
type User = '["userId" ::: 'NotNull 'PGint2, "userName" ::: 'Null 'PGtext]
>>>
fromRow @User @UserRow (K (Just "\NUL\SOH") :* K (Just "bloodninja") :* Nil)
Right (UserRow {userId = UserId {getUserId = 1}, userName = Just "bloodninja"})
Only
Only
is a 1-tuple type, useful for encoding a single parameter with
toParams
or decoding a single value with fromRow
.
>>>
import Data.Text
>>>
toParams @(Only (Maybe Text)) @'[ 'Null 'PGtext] (Only (Just "foo"))
K (Just "foo") :* Nil
>>>
fromRow @'["fromOnly" ::: 'Null 'PGtext] @(Only (Maybe Text)) (K (Just "bar") :* Nil)
Right (Only {fromOnly = Just "bar"})