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.
>>>
import Data.Int (Int16)
>>>
import Data.Text (Text)
>>>
data Row = Row { col1 :: Int16, col2 :: Text } deriving (Eq, GHC.Generic)
>>>
instance Generic Row
>>>
instance HasDatatypeInfo Row
>>>
import Control.Monad (void)
>>>
import Control.Monad.Base (liftBase)
>>>
import Squeal.PostgreSQL
>>>
:{
let query :: Query '[] '[ 'NotNull 'PGint2, 'NotNull 'PGtext] '["col1" ::: 'NotNull 'PGint2, "col2" ::: 'NotNull 'PGtext] query = values_ (param @1 `as` #col1 :* param @2 `as` #col2) :}
>>>
:{
let roundtrip :: IO () roundtrip = void . withConnection "host=localhost port=5432 dbname=exampledb" $ do result <- runQueryParams query (2 :: Int16, "hi" :: Text) Just row <- firstRow result liftBase . print $ row == Row 2 "hi" :}
>>>
roundtrip
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 which are equivalent to
Postgres enumerated and composite types.
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 (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. They are almost
equivalent to Haskell record types. However, because of the potential presence of NULL
all the record fields must be Maybe
s of basic types.
>>>
data Person = Person {name :: Maybe Text, age :: Maybe Int32} deriving (Show, GHC.Generic)
>>>
instance Generic Person
>>>
instance HasDatatypeInfo Person
We can create the equivalent Postgres types directly from their Haskell types.
>>>
:{
type Schema = '[ "schwarma" ::: 'Typedef (EnumFrom Schwarma) , "person" ::: 'Typedef (CompositeFrom Person) ] :}
>>>
:{
let setup :: Definition '[] Schema setup = createTypeEnumFrom @Schwarma #schwarma >>> createTypeCompositeFrom @Person #person :}
Then we can perform roundtrip queries;
>>>
:{
let querySchwarma :: Query Schema '[ 'NotNull (EnumFrom Schwarma)] '["fromOnly" ::: 'NotNull (EnumFrom Schwarma)] querySchwarma = values_ (parameter @1 #schwarma `as` #fromOnly) :}
>>>
:{
let queryPerson :: Query Schema '[ 'NotNull (CompositeFrom Person)] '["fromOnly" ::: 'NotNull (CompositeFrom Person)] queryPerson = values_ (parameter @1 #person `as` #fromOnly) :}
And finally drop the types.
>>>
:{
let teardown :: Definition Schema '[] teardown = dropType #schwarma >>> dropType #person :}
Now let's run it.
>>>
:{
let session = do result1 <- runQueryParams querySchwarma (Only Chicken) Just (Only schwarma) <- firstRow result1 liftBase $ print (schwarma :: Schwarma) result2 <- runQueryParams queryPerson (Only (Person (Just "Faisal") (Just 24))) Just (Only person) <- firstRow result2 liftBase $ print (person :: Person) in void . withConnection "host=localhost port=5432 dbname=exampledb" $ define setup & pqThen session & pqThen (define teardown) :} Chicken Person {name = Just "Faisal", age = Just 24}
Synopsis
- class ToParam (x :: Type) (pg :: PGType) where
- class ToColumnParam (x :: Type) (ty :: NullityType) where
- class SListI tys => ToParams (x :: Type) (tys :: [NullityType]) where
- class FromValue (pg :: PGType) (y :: Type) where
- class FromColumnValue (colty :: (Symbol, NullityType)) (y :: Type) where
- class SListI results => FromRow (results :: RelationType) y where
- newtype Only x = Only {
- fromOnly :: x
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 ToColumnParam (x :: Type) (ty :: NullityType) where Source #
A ToColumnParam
constraint lifts the ToParam
encoding
of a Type
to a NullityType
, encoding Maybe
s to Null
s. You should
not define instances of ToColumnParam
, just use the provided instances.
Minimal complete definition
Methods
toColumnParam :: x -> K (Maybe ByteString) ty Source #
>>>
toColumnParam @Int16 @('NotNull 'PGint2) 0
K (Just "\NUL\NUL")
>>>
toColumnParam @(Maybe Int16) @('Null 'PGint2) (Just 0)
K (Just "\NUL\NUL")
>>>
toColumnParam @(Maybe Int16) @('Null 'PGint2) Nothing
K Nothing
Instances
ToParam x pg => ToColumnParam x (NotNull pg) Source # | |
Defined in Squeal.PostgreSQL.Binary Methods toColumnParam :: x -> K (Maybe ByteString) (NotNull pg) Source # | |
ToParam x pg => ToColumnParam (Maybe x) (Null pg) Source # | |
Defined in Squeal.PostgreSQL.Binary Methods toColumnParam :: Maybe x -> K (Maybe ByteString) (Null pg) Source # |
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 ByteString)) 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
Instances
(SListI tys, IsProductType x xs, AllZip ToColumnParam xs tys) => ToParams x tys Source # | |
Defined in Squeal.PostgreSQL.Binary |
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
fromValue :: proxy pg -> Value y Source #
>>>
newtype Id = Id { getId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 Id where fromValue = fmap Id . fromValue
Instances
class FromColumnValue (colty :: (Symbol, NullityType)) (y :: Type) where Source #
A FromColumnValue
constraint lifts the FromValue
parser
to a decoding of a (Symbol, NullityType)
to a Type
,
decoding Null
s to Maybe
s. You should not define instances for
FromColumnValue
, just use the provided instances.
Minimal complete definition
Methods
fromColumnValue :: K (Maybe ByteString) colty -> y Source #
>>>
:set -XTypeOperators -XOverloadedStrings
>>>
newtype Id = Id { getId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 Id where fromValue = fmap Id . fromValue
>>>
fromColumnValue @("col" ::: 'NotNull 'PGint2) @Id (K (Just "\NUL\SOH"))
Id {getId = 1}
>>>
fromColumnValue @("col" ::: 'Null 'PGint2) @(Maybe Id) (K (Just "\NUL\SOH"))
Just (Id {getId = 1})
Instances
FromValue pg y => FromColumnValue (column ::: NotNull pg) y Source # | |
Defined in Squeal.PostgreSQL.Binary Methods fromColumnValue :: K (Maybe ByteString) (column ::: NotNull pg) -> y Source # | |
FromValue pg y => FromColumnValue (column ::: Null pg) (Maybe y) Source # | |
Defined in Squeal.PostgreSQL.Binary Methods fromColumnValue :: K (Maybe ByteString) (column ::: Null pg) -> Maybe y Source # |
class SListI results => FromRow (results :: RelationType) y where Source #
A FromRow
constraint generically sequences the parsings of the columns
of a RelationType
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)) results -> y Source #
>>>
:set -XOverloadedStrings
>>>
import Data.Text
>>>
newtype UserId = UserId { getUserId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 UserId where fromValue = fmap UserId . fromValue
>>>
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)
UserRow {userId = UserId {getUserId = 1}, userName = Just "bloodninja"}
Instances
(SListI results, IsProductType y ys, AllZip FromColumnValue results ys, FieldNamesFrom y ~ AliasesOf results) => FromRow results y Source # | |
Defined in Squeal.PostgreSQL.Binary |
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)
Only {fromOnly = Just "bar"}