module Hasql.Private.Decoders
where
import Hasql.Private.Prelude hiding (maybe, bool)
import qualified Data.Vector as Vector
import qualified PostgreSQL.Binary.Decoding as A
import qualified PostgreSQL.Binary.Data as B
import qualified Hasql.Private.Decoders.Results as Results
import qualified Hasql.Private.Decoders.Result as Result
import qualified Hasql.Private.Decoders.Row as Row
import qualified Hasql.Private.Decoders.Value as Value
import qualified Hasql.Private.Decoders.Array as Array
import qualified Hasql.Private.Decoders.Composite as Composite
import qualified Hasql.Private.Prelude as Prelude
import qualified Data.Vector.Generic as GenericVector
newtype Result a = Result (Results.Results a) deriving (Functor)
{-# INLINABLE noResult #-}
noResult :: Result ()
noResult = Result (Results.single Result.noResult)
{-# INLINABLE rowsAffected #-}
rowsAffected :: Result Int64
rowsAffected = Result (Results.single Result.rowsAffected)
{-# INLINABLE singleRow #-}
singleRow :: Row a -> Result a
singleRow (Row row) = Result (Results.single (Result.single row))
refineResult :: (a -> Either Text b) -> Result a -> Result b
refineResult refiner (Result results) = Result (Results.refine refiner results)
{-# INLINABLE foldlRows #-}
foldlRows :: (a -> b -> a) -> a -> Row b -> Result a
foldlRows step init (Row row) = Result (Results.single (Result.foldl step init row))
{-# INLINABLE foldrRows #-}
foldrRows :: (b -> a -> a) -> a -> Row b -> Result a
foldrRows step init (Row row) = Result (Results.single (Result.foldr step init row))
{-# INLINABLE rowMaybe #-}
rowMaybe :: Row a -> Result (Maybe a)
rowMaybe (Row row) = Result (Results.single (Result.maybe row))
{-# INLINABLE rowVector #-}
rowVector :: Row a -> Result (Vector a)
rowVector (Row row) = Result (Results.single (Result.vector row))
{-# INLINABLE rowList #-}
rowList :: Row a -> Result [a]
rowList = foldrRows strictCons []
newtype Row a = Row (Row.Row a)
deriving (Functor, Applicative, Monad)
{-# INLINABLE column #-}
column :: NullableOrNot Value a -> Row a
column = \ case
NonNullable (Value imp) -> Row (Row.nonNullValue imp)
Nullable (Value imp) -> Row (Row.value imp)
data NullableOrNot decoder a where
NonNullable :: decoder a -> NullableOrNot decoder a
Nullable :: decoder a -> NullableOrNot decoder (Maybe a)
nonNullable :: decoder a -> NullableOrNot decoder a
nonNullable = NonNullable
nullable :: decoder a -> NullableOrNot decoder (Maybe a)
nullable = Nullable
newtype Value a = Value (Value.Value a)
deriving (Functor)
{-# INLINABLE bool #-}
bool :: Value Bool
bool = Value (Value.decoder (const A.bool))
{-# INLINABLE int2 #-}
int2 :: Value Int16
int2 = Value (Value.decoder (const A.int))
{-# INLINABLE int4 #-}
int4 :: Value Int32
int4 = Value (Value.decoder (const A.int))
{-# INLINABLE int8 #-}
int8 :: Value Int64
int8 = {-# SCC "int8" #-}
Value (Value.decoder (const ({-# SCC "int8.int" #-} A.int)))
{-# INLINABLE float4 #-}
float4 :: Value Float
float4 = Value (Value.decoder (const A.float4))
{-# INLINABLE float8 #-}
float8 :: Value Double
float8 = Value (Value.decoder (const A.float8))
{-# INLINABLE numeric #-}
numeric :: Value B.Scientific
numeric = Value (Value.decoder (const A.numeric))
{-# INLINABLE char #-}
char :: Value Char
char = Value (Value.decoder (const A.char))
{-# INLINABLE text #-}
text :: Value Text
text = Value (Value.decoder (const A.text_strict))
{-# INLINABLE bytea #-}
bytea :: Value ByteString
bytea = Value (Value.decoder (const A.bytea_strict))
{-# INLINABLE date #-}
date :: Value B.Day
date = Value (Value.decoder (const A.date))
{-# INLINABLE timestamp #-}
timestamp :: Value B.LocalTime
timestamp = Value (Value.decoder (Prelude.bool A.timestamp_float A.timestamp_int))
{-# INLINABLE timestamptz #-}
timestamptz :: Value B.UTCTime
timestamptz = Value (Value.decoder (Prelude.bool A.timestamptz_float A.timestamptz_int))
{-# INLINABLE time #-}
time :: Value B.TimeOfDay
time = Value (Value.decoder (Prelude.bool A.time_float A.time_int))
{-# INLINABLE timetz #-}
timetz :: Value (B.TimeOfDay, B.TimeZone)
timetz = Value (Value.decoder (Prelude.bool A.timetz_float A.timetz_int))
{-# INLINABLE interval #-}
interval :: Value B.DiffTime
interval = Value (Value.decoder (Prelude.bool A.interval_float A.interval_int))
{-# INLINABLE uuid #-}
uuid :: Value B.UUID
uuid = Value (Value.decoder (const A.uuid))
{-# INLINABLE inet #-}
inet :: Value (B.NetAddr B.IP)
inet = Value (Value.decoder (const A.inet))
{-# INLINABLE json #-}
json :: Value B.Value
json = Value (Value.decoder (const A.json_ast))
{-# INLINABLE jsonBytes #-}
jsonBytes :: (ByteString -> Either Text a) -> Value a
jsonBytes fn = Value (Value.decoder (const (A.json_bytes fn)))
{-# INLINABLE jsonb #-}
jsonb :: Value B.Value
jsonb = Value (Value.decoder (const A.jsonb_ast))
{-# INLINABLE jsonbBytes #-}
jsonbBytes :: (ByteString -> Either Text a) -> Value a
jsonbBytes fn = Value (Value.decoder (const (A.jsonb_bytes fn)))
{-# INLINABLE custom #-}
custom :: (Bool -> ByteString -> Either Text a) -> Value a
custom fn = Value (Value.decoderFn fn)
{-# INLINABLE refine #-}
refine :: (a -> Either Text b) -> Value a -> Value b
refine fn (Value v) = Value (Value.Value (ask >>= \b -> lift (A.refine fn (Value.run v b))))
{-# INLINABLE hstore #-}
hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a
hstore replicateM = Value (Value.decoder (const (A.hstore replicateM A.text_strict A.text_strict)))
enum :: (Text -> Maybe a) -> Value a
enum mapping = Value (Value.decoder (const (A.enum mapping)))
{-# INLINABLE array #-}
array :: Array a -> Value a
array (Array imp) = Value (Value.decoder (Array.run imp))
{-# INLINE listArray #-}
listArray :: NullableOrNot Value element -> Value [element]
listArray = array . dimension replicateM . element
{-# INLINE vectorArray #-}
vectorArray :: GenericVector.Vector vector element => NullableOrNot Value element -> Value (vector element)
vectorArray = array . dimension GenericVector.replicateM . element
{-# INLINABLE composite #-}
composite :: Composite a -> Value a
composite (Composite imp) = Value (Value.decoder (Composite.run imp))
newtype Array a = Array (Array.Array a)
deriving (Functor)
{-# INLINABLE dimension #-}
dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
dimension replicateM (Array imp) = Array (Array.dimension replicateM imp)
{-# INLINABLE element #-}
element :: NullableOrNot Value a -> Array a
element = \ case
NonNullable (Value imp) -> Array (Array.nonNullValue (Value.run imp))
Nullable (Value imp) -> Array (Array.value (Value.run imp))
newtype Composite a = Composite (Composite.Composite a)
deriving (Functor, Applicative, Monad)
field :: NullableOrNot Value a -> Composite a
field = \ case
NonNullable (Value imp) -> Composite (Composite.nonNullValue (Value.run imp))
Nullable (Value imp) -> Composite (Composite.value (Value.run imp))