Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Binary
Description
Binary encoding and decoding between Haskell and PostgreSQL types.
- class ToParam (x :: Type) (pg :: PGType) where
- class ToColumnParam (x :: Type) (ty :: ColumnType) where
- class SListI tys => ToParams (x :: Type) (tys :: [ColumnType]) where
- class FromValue (pg :: PGType) (y :: Type) where
- class FromColumnValue (colty :: (Symbol, ColumnType)) (y :: Type) where
- class SListI results => FromRow (results :: ColumnsType) 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 :: ColumnType) where Source #
A ToColumnParam
constraint lifts the ToParam
encoding
of a Type
to a ColumnType
, 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 @('Required ('NotNull 'PGint2)) 0
K (Just "\NUL\NUL")
>>>
toColumnParam @(Maybe Int16) @('Required ('Null 'PGint2)) (Just 0)
K (Just "\NUL\NUL")
>>>
toColumnParam @(Maybe Int16) @('Required ('Null 'PGint2)) Nothing
K Nothing
class SListI tys => ToParams (x :: Type) (tys :: [ColumnType]) 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 PGparams = '[ 'Required ('NotNull 'PGbool), 'Required ('Null 'PGint2)]
>>>
toParams @(Bool, Maybe Int16) @PGparams (False, Just 0)
K (Just "\NUL") :* (K (Just "\NUL\NUL") :* Nil)
>>>
:set -XDeriveGeneric
>>>
data Hparams = Hparams { col1 :: Bool, col2 :: Maybe Int16} deriving GHC.Generic
>>>
instance Generic Hparams
>>>
toParams @Hparams @PGparams (Hparams False (Just 0))
K (Just "\NUL") :* (K (Just "\NUL\NUL") :* Nil)
Instances
(SListI ColumnType tys, IsProductType x xs, AllZip Type ColumnType ToColumnParam xs tys) => ToParams x tys Source # | |
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, ColumnType)) (y :: Type) where Source #
A FromColumnValue
constraint lifts the FromValue
parser
to a decoding of a (Symbol, ColumnType)
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" ::: 'Required ('NotNull 'PGint2)) @Id (K (Just "\NUL\SOH"))
Id {getId = 1}
>>>
fromColumnValue @("col" ::: 'Required ('Null 'PGint2)) @(Maybe Id) (K (Just "\NUL\SOH"))
Just (Id {getId = 1})
Instances
FromValue pg y => FromColumnValue ((:::) ColumnType column (Required (NotNull pg))) y Source # | |
FromValue pg y => FromColumnValue ((:::) ColumnType column (Required (Null pg))) (Maybe y) Source # | |
class SListI results => FromRow (results :: ColumnsType) y where Source #
A FromRow
constraint generically sequences the parsings of the columns
of a ColumnsType
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 Id = Id { getId :: Int16 } deriving Show
>>>
instance FromValue 'PGint2 Id where fromValue = fmap Id . fromValue
>>>
data Hrow = Hrow { userId :: Id, userName :: Maybe Text } deriving (Show, GHC.Generic)
>>>
instance Generic Hrow
>>>
instance HasDatatypeInfo Hrow
>>>
type PGrow = '["userId" ::: 'Required ('NotNull 'PGint2), "userName" ::: 'Required ('Null 'PGtext)]
>>>
fromRow @PGrow @Hrow (K (Just "\NUL\SOH") :* K (Just "bloodninja") :* Nil)
Hrow {userId = Id {getId = 1}, userName = Just "bloodninja"}
Instances
(SListI (Symbol, ColumnType) results, IsProductType y ys, AllZip (Symbol, ColumnType) Type FromColumnValue results ys, SameFields (DatatypeInfoOf y) results) => FromRow results y Source # | |
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)) @'[ 'Required ('Null 'PGtext)] (Only (Just "foo"))
K (Just "foo") :* Nil
>>>
type PGShortRow = '["fromOnly" ::: 'Required ('Null 'PGtext)]
>>>
fromRow @PGShortRow @(Only (Maybe Text)) (K (Just "bar") :* Nil)
Only {fromOnly = Just "bar"}
Instances
Functor Only Source # | |
Foldable Only Source # | |
Traversable Only Source # | |
Eq x => Eq (Only x) Source # | |
Ord x => Ord (Only x) Source # | |
Read x => Read (Only x) Source # | |
Show x => Show (Only x) Source # | |
Generic (Only x) Source # | |
Generic (Only x) Source # | |
HasDatatypeInfo (Only x) Source # | |
type Rep (Only x) Source # | |
type Code (Only x) Source # | |
type DatatypeInfoOf (Only x) Source # | |