{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasql.Interpolate.Internal.Decoder
(
DecodeValue (..),
DecodeField (..),
DecodeRow (..),
DecodeResult (..),
GDecodeRow (..),
)
where
import Data.Int
import Data.Scientific (Scientific)
import Data.Text (Text)
import Data.Time (Day, DiffTime, LocalTime, UTCTime)
import Data.UUID (UUID)
import Data.Vector (Vector)
import GHC.Generics
import Hasql.Decoders
import Hasql.Interpolate.Internal.Decoder.TH
class DecodeValue a where
decodeValue :: Value a
class DecodeField a where
decodeField :: NullableOrNot Value a
class DecodeRow a where
decodeRow :: Row a
default decodeRow :: (Generic a, GDecodeRow (Rep a)) => Row a
decodeRow = forall a x. Generic a => Rep a x -> a
to forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: * -> *) p. GDecodeRow a => Row (a p)
gdecodeRow
class GDecodeRow a where
gdecodeRow :: Row (a p)
class DecodeResult a where
decodeResult :: Result a
instance GDecodeRow a => GDecodeRow (M1 t i a) where
gdecodeRow :: forall p. Row (M1 t i a p)
gdecodeRow = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: * -> *) p. GDecodeRow a => Row (a p)
gdecodeRow
instance (GDecodeRow a, GDecodeRow b) => GDecodeRow (a :*: b) where
gdecodeRow :: forall p. Row ((:*:) a b p)
gdecodeRow = forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: * -> *) p. GDecodeRow a => Row (a p)
gdecodeRow forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (a :: * -> *) p. GDecodeRow a => Row (a p)
gdecodeRow
instance DecodeField a => GDecodeRow (K1 i a) where
gdecodeRow :: forall p. Row (K1 i a p)
gdecodeRow = forall k i c (p :: k). c -> K1 i c p
K1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. NullableOrNot Value a -> Row a
column forall a. DecodeField a => NullableOrNot Value a
decodeField
instance DecodeField a => DecodeValue [a] where
decodeValue :: Value [a]
decodeValue = forall element. NullableOrNot Value element -> Value [element]
listArray forall a. DecodeField a => NullableOrNot Value a
decodeField
instance DecodeField a => DecodeValue (Vector a) where
decodeValue :: Value (Vector a)
decodeValue = forall (vector :: * -> *) element.
Vector vector element =>
NullableOrNot Value element -> Value (vector element)
vectorArray forall a. DecodeField a => NullableOrNot Value a
decodeField
instance DecodeValue Bool where
decodeValue :: Value Bool
decodeValue = Value Bool
bool
instance DecodeValue Text where
decodeValue :: Value Text
decodeValue = Value Text
text
instance DecodeValue Int16 where
decodeValue :: Value Int16
decodeValue = Value Int16
int2
instance DecodeValue Int32 where
decodeValue :: Value Int32
decodeValue = Value Int32
int4
instance DecodeValue Int64 where
decodeValue :: Value Int64
decodeValue = Value Int64
int8
instance DecodeValue Float where
decodeValue :: Value Float
decodeValue = Value Float
float4
instance DecodeValue Double where
decodeValue :: Value Double
decodeValue = Value Double
float8
instance DecodeValue Char where
decodeValue :: Value Char
decodeValue = Value Char
char
instance DecodeValue Day where
decodeValue :: Value Day
decodeValue = Value Day
date
instance DecodeValue LocalTime where
decodeValue :: Value LocalTime
decodeValue = Value LocalTime
timestamp
instance DecodeValue UTCTime where
decodeValue :: Value UTCTime
decodeValue = Value UTCTime
timestamptz
instance DecodeValue Scientific where
decodeValue :: Value Scientific
decodeValue = Value Scientific
numeric
instance DecodeValue DiffTime where
decodeValue :: Value DiffTime
decodeValue = Value DiffTime
interval
instance DecodeValue UUID where
decodeValue :: Value UUID
decodeValue = Value UUID
uuid
instance {-# OVERLAPPABLE #-} DecodeValue a => DecodeField a where
decodeField :: NullableOrNot Value a
decodeField = forall (decoder :: * -> *) a. decoder a -> NullableOrNot decoder a
nonNullable forall a. DecodeValue a => Value a
decodeValue
instance DecodeValue a => DecodeField (Maybe a) where
decodeField :: NullableOrNot Value (Maybe a)
decodeField = forall (decoder :: * -> *) a.
decoder a -> NullableOrNot decoder (Maybe a)
nullable forall a. DecodeValue a => Value a
decodeValue
instance DecodeRow a => DecodeResult [a] where
decodeResult :: Result [a]
decodeResult = forall a. Row a -> Result [a]
rowList forall a. DecodeRow a => Row a
decodeRow
instance DecodeRow a => DecodeResult (Vector a) where
decodeResult :: Result (Vector a)
decodeResult = forall a. Row a -> Result (Vector a)
rowVector forall a. DecodeRow a => Row a
decodeRow
instance DecodeRow a => DecodeResult (Maybe a) where
decodeResult :: Result (Maybe a)
decodeResult = forall a. Row a -> Result (Maybe a)
rowMaybe forall a. DecodeRow a => Row a
decodeRow
instance DecodeResult () where
decodeResult :: Result ()
decodeResult = Result ()
noResult
$(traverse genDecodeRowInstance [2 .. 8])