Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- enumValue :: (All KnownSymbol labels, PG y ~ 'PGenum labels) => NP (K y) labels -> 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
- class (IsRecord y ys, row ~ RowPG y, AllZip FromField row ys) => GenericRow row y ys where
- genericRow :: DecodeRow row y
- genericProductRow :: (IsProductType y ys, AllZip FromAliasedValue row ys) => DecodeRow row y
- appendRows :: SListI left => (l -> r -> z) -> DecodeRow left l -> DecodeRow right r -> DecodeRow (Join left right) z
- consRow :: FromValue head h => (h -> t -> z) -> Alias col -> DecodeRow tail t -> DecodeRow ((col ::: head) ': tail) z
- class FromValue (ty :: NullType) (y :: Type) where
- fromValue :: Maybe ByteString -> Either Text y
- class FromField (field :: (Symbol, NullType)) (y :: (Symbol, Type)) where
- class FromAliasedValue (field :: (Symbol, NullType)) (y :: Type) where
- fromAliasedValue :: Maybe ByteString -> Either Text y
- 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
.
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
:: (PG y ~ 'PGcomposite row, SListI row) | |
=> DecodeRow row y | fields |
-> StateT ByteString (Except Text) y |
>>>
: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} :}
:: (All KnownSymbol labels, PG y ~ 'PGenum labels) | |
=> NP (K y) labels | labels |
-> StateT ByteString (Except Text) y |
>>>
:{
data Dir = North | East | South | West instance IsPG Dir where type PG Dir = 'PGenum '["north", "south", "east", "west"] instance FromPG Dir where fromPG = enumValue $ label @"north" North :* label @"south" South :* label @"east" East :* label @"west" West :}
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'))
DecodeRow | |
|
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
.
class (IsRecord y ys, row ~ RowPG y, AllZip FromField row ys) => GenericRow row y ys where Source #
A GenericRow
constraint to ensure that a Haskell type
is a record type,
has a RowPG
,
and all its fields and can be decoded from corresponding Postgres fields.
genericRow :: 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"})
Instances
(row ~ RowPG y, IsRecord y ys, AllZip FromField row ys) => GenericRow row y ys Source # | |
Defined in Squeal.PostgreSQL.Session.Decode genericRow :: DecodeRow row y Source # |
genericProductRow :: (IsProductType y ys, AllZip FromAliasedValue row ys) => DecodeRow row y Source #
Positionally DecodeRow
. More general than genericRow
,
which matches records both positionally and by field name,
genericProductRow
matches records _or_ tuples purely positionally.
>>>
import qualified GHC.Generics as GHC
>>>
import qualified Generics.SOP as SOP
>>>
:{
let decode :: DecodeRow '[ "foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGtext] (Int16, String) decode = genericProductRow in runDecodeRow decode (SOP.K (Just "\NUL\STX") :* SOP.K (Just "two") :* Nil) :} Right (2,"two")
:: SListI left | |
=> (l -> r -> z) | combining function |
-> DecodeRow left l | left decoder |
-> DecodeRow right r | right decoder |
-> DecodeRow (Join left right) z |
Append two row decoders with a combining function.
>>>
import GHC.Generics as GHC
>>>
:{
data L = L {fst :: Int16, snd :: 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) type Row = '[ "fst" ::: 'NotNull 'PGint2, "snd" ::: 'NotNull ('PGchar 1), "thrd" ::: 'NotNull 'PGbool, "frth" ::: 'NotNull 'PGbool] :}
>>>
:{
let decode :: DecodeRow Row (L,R) decode = appendRows (,) genericRow genericRow row4 = SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* SOP.K (Just "\NUL") :* SOP.K (Just "\NUL") :* Nil in runDecodeRow decode row4 :} Right (L {fst = 1, snd = 'a'},R {thrd = False, frth = False})
:: FromValue head h | |
=> (h -> t -> z) | combining function |
-> Alias col | alias of head |
-> DecodeRow tail t | tail decoder |
-> DecodeRow ((col ::: head) ': tail) z |
Cons a column and a row decoder with a combining function.
>>>
:{
let decode :: DecodeRow '["fst" ::: 'NotNull 'PGtext, "snd" ::: 'NotNull 'PGint2, "thrd" ::: 'NotNull ('PGchar 1)] (String, (Int16, Char)) decode = consRow (,) #fst (consRow (,) #snd #thrd) in runDecodeRow decode (SOP.K (Just "hi") :* SOP.K (Just "\NUL\SOH") :* SOP.K (Just "a") :* Nil) :} Right ("hi",(1,'a'))
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 FromAliasedValue (field :: (Symbol, NullType)) (y :: Type) where Source #
Assistant class for genericProductRow
,
this class forgets the name of a field while decoding it.
fromAliasedValue :: Maybe ByteString -> Either Text y Source #
Instances
FromValue ty y => FromAliasedValue (fld ::: ty) y Source # | |
Defined in Squeal.PostgreSQL.Session.Decode fromAliasedValue :: Maybe ByteString -> Either Text y 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.