Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Session.Decode
Description
decoding of result values
Synopsis
- class IsPG y => FromPG y where
- fromPG :: StateT ByteString (Except Text) y
- devalue :: Value x -> StateT ByteString (Except Text) x
- rowValue :: (PG y ~ PGcomposite row, SListI row) => DecodeRow row y -> StateT ByteString (Except Text) y
- newtype DecodeRow (row :: RowType) (y :: Type) = DecodeRow {
- unDecodeRow :: ReaderT (NP (K (Maybe ByteString)) row) (Except Text) y
- decodeRow :: (NP (K (Maybe ByteString)) row -> Either Text y) -> DecodeRow row y
- runDecodeRow :: DecodeRow row y -> NP (K (Maybe ByteString)) row -> Either Text y
- genericRow :: forall row y ys. (IsRecord y ys, AllZip FromField row ys) => DecodeRow row y
- class FromValue (ty :: NullType) (y :: Type) where
- fromValue :: Maybe ByteString -> Either Text y
- class FromField (field :: (Symbol, NullType)) (y :: (Symbol, Type)) where
- class FromArray (dims :: [Nat]) (ty :: NullType) (y :: Type) where
- newtype StateT s (m :: Type -> Type) a = StateT {
- runStateT :: s -> m (a, s)
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
Decode Types
class IsPG y => FromPG y where Source #
A FromPG
constraint gives a parser from the binary format of
a PostgreSQL PGType
into a Haskell Type
.
Methods
fromPG :: StateT ByteString (Except Text) y Source #
>>>
:set -XMultiParamTypeClasses -XGeneralizedNewtypeDeriving -XDerivingStrategies -XDerivingVia -XUndecidableInstances
>>>
import GHC.Generics as GHC
>>>
:{
newtype UserId = UserId { getId :: Int64 } deriving newtype (IsPG, FromPG) :}
>>>
:{
data Complex = Complex { real :: Double , imaginary :: Double } deriving stock GHC.Generic deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) deriving (IsPG, FromPG) via (Composite Complex) :}
>>>
:{
data Direction = North | South | East | West deriving stock GHC.Generic deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) deriving (IsPG, FromPG) via (Enumerated Direction) :}
Instances
rowValue :: (PG y ~ PGcomposite row, SListI row) => DecodeRow row y -> StateT ByteString (Except Text) y Source #
>>>
:set -XTypeFamilies
>>>
:{
data Complex = Complex { real :: Double , imaginary :: Double } instance IsPG Complex where type PG Complex = 'PGcomposite '[ "re" ::: 'NotNull 'PGfloat8, "im" ::: 'NotNull 'PGfloat8] instance FromPG Complex where fromPG = rowValue $ do re <- #re im <- #im return Complex {real = re, imaginary = im} :}
Decode Rows
newtype DecodeRow (row :: RowType) (y :: Type) Source #
DecodeRow
describes a decoding of a PostgreSQL RowType
into a Haskell Type
.
DecodeRow
has an interface given by the classes
Functor
, Applicative
, Alternative
, Monad
,
MonadPlus
, MonadError
Text
, and IsLabel
.
>>>
:set -XOverloadedLabels
>>>
:{
let decode :: DecodeRow '[ "fst" ::: 'NotNull 'PGint2, "snd" ::: 'NotNull ('PGchar 1)] (Int16, Char) decode = (,) <$> #fst <*> #snd in runDecodeRow decode (SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil) :} Right (1,'a')
There is also an IsLabel
instance for MaybeT
DecodeRow
s, useful
for decoding outer joined rows.
>>>
:{
let decode :: DecodeRow '[ "fst" ::: 'Null 'PGint2, "snd" ::: 'Null ('PGchar 1)] (Maybe (Int16, Char)) decode = runMaybeT $ (,) <$> #fst <*> #snd in runDecodeRow decode (SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil) :} Right (Just (1,'a'))
Constructors
DecodeRow | |
Fields
|
Instances
decodeRow :: (NP (K (Maybe ByteString)) row -> Either Text y) -> DecodeRow row y Source #
Smart constructor for a DecodeRow
.
runDecodeRow :: DecodeRow row y -> NP (K (Maybe ByteString)) row -> Either Text y Source #
Run a DecodeRow
.
genericRow :: forall row y ys. (IsRecord y ys, AllZip FromField row ys) => DecodeRow row y Source #
Row decoder for Generic
records.
>>>
import qualified GHC.Generics as GHC
>>>
import qualified Generics.SOP as SOP
>>>
data Two = Two {frst :: Int16, scnd :: String} deriving (Show, GHC.Generic, SOP.Generic, SOP.HasDatatypeInfo)
>>>
:{
let decode :: DecodeRow '[ "frst" ::: 'NotNull 'PGint2, "scnd" ::: 'NotNull 'PGtext] Two decode = genericRow in runDecodeRow decode (SOP.K (Just "\NUL\STX") :* SOP.K (Just "two") :* Nil) :} Right (Two {frst = 2, scnd = "two"})
Decoding Classes
class FromValue (ty :: NullType) (y :: Type) where Source #
A FromValue
constraint lifts the FromPG
parser
to a decoding of a NullityType
to a Type
,
decoding Null
s to Maybe
s. You should not define instances for
FromValue
, just use the provided instances.
class FromField (field :: (Symbol, NullType)) (y :: (Symbol, Type)) where Source #
class FromArray (dims :: [Nat]) (ty :: NullType) (y :: Type) where Source #
A FromArray
constraint gives a decoding to a Haskell Type
from the binary format of a PostgreSQL fixed-length array.
You should not define instances for
FromArray
, just use the provided instances.
Instances
(FromPG y, pg ~ PG y) => FromArray ([] :: [Nat]) (NotNull pg) y Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
(FromPG y, pg ~ PG y) => FromArray ([] :: [Nat]) (Null pg) (Maybe y) Source # | |
(IsProductType product ys, Length ys ~ dim, All (Type ~ y) ys, FromArray dims ty y) => FromArray (dim ': dims) ty product Source # | |
Defined in Squeal.PostgreSQL.Session.Decode |
newtype StateT s (m :: Type -> Type) a #
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
newtype ExceptT e (m :: Type -> Type) a #
A monad transformer that adds exceptions to other monads.
ExceptT
constructs a monad parameterized over two things:
- e - The exception type.
- m - The inner monad.
The return
function yields a computation that produces the given
value, while >>=
sequences two subcomputations, exiting on the
first exception.