hasql/library/Hasql/Private/Decoders.hs

408 lines
12 KiB
Haskell
Raw Normal View History

2022-06-20 13:54:54 +03:00
-- |
-- A DSL for declaration of result decoders.
module Hasql.Private.Decoders where
2019-05-21 01:20:57 +03:00
import qualified Data.Aeson as Aeson
2022-06-20 13:54:54 +03:00
import qualified Data.Vector.Generic as GenericVector
import qualified Hasql.Private.Decoders.Array as Array
import qualified Hasql.Private.Decoders.Composite as Composite
2019-05-21 01:20:57 +03:00
import qualified Hasql.Private.Decoders.Result as Result
2022-06-20 13:54:54 +03:00
import qualified Hasql.Private.Decoders.Results as Results
2019-05-21 01:20:57 +03:00
import qualified Hasql.Private.Decoders.Row as Row
import qualified Hasql.Private.Decoders.Value as Value
2022-06-20 13:54:54 +03:00
import Hasql.Private.Prelude hiding (bool, maybe)
2019-05-21 01:20:57 +03:00
import qualified Hasql.Private.Prelude as Prelude
import qualified Network.IP.Addr as NetworkIp
2022-06-20 13:54:54 +03:00
import qualified PostgreSQL.Binary.Decoding as A
2019-05-21 01:20:57 +03:00
-- * Result
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of a query result.
2019-05-21 01:20:57 +03:00
newtype Result a = Result (Results.Results a) deriving (Functor)
2022-06-20 13:54:54 +03:00
-- |
-- Decode no value from the result.
--
-- Useful for statements like @INSERT@ or @CREATE@.
{-# INLINEABLE noResult #-}
2019-05-21 13:25:22 +03:00
noResult :: Result ()
noResult = Result (Results.single Result.noResult)
2019-05-21 01:20:57 +03:00
2022-06-20 13:54:54 +03:00
-- |
-- Get the amount of rows affected by such statements as
-- @UPDATE@ or @DELETE@.
{-# INLINEABLE rowsAffected #-}
2019-05-21 01:20:57 +03:00
rowsAffected :: Result Int64
rowsAffected = Result (Results.single Result.rowsAffected)
2022-06-20 13:54:54 +03:00
-- |
-- Exactly one row.
-- Will raise the 'Errors.UnexpectedAmountOfRows' error if it's any other.
{-# INLINEABLE singleRow #-}
2019-05-21 01:20:57 +03:00
singleRow :: Row a -> Result a
singleRow (Row row) = Result (Results.single (Result.single row))
2020-03-21 20:54:13 +03:00
refineResult :: (a -> Either Text b) -> Result a -> Result b
refineResult refiner (Result results) = Result (Results.refine refiner results)
2019-05-21 01:20:57 +03:00
-- ** Multi-row traversers
2022-06-20 13:54:54 +03:00
-- |
-- Foldl multiple rows.
{-# INLINEABLE foldlRows #-}
2019-05-21 01:20:57 +03:00
foldlRows :: (a -> b -> a) -> a -> Row b -> Result a
foldlRows step init (Row row) = Result (Results.single (Result.foldl step init row))
2022-06-20 13:54:54 +03:00
-- |
-- Foldr multiple rows.
{-# INLINEABLE foldrRows #-}
2019-05-21 01:20:57 +03:00
foldrRows :: (b -> a -> a) -> a -> Row b -> Result a
foldrRows step init (Row row) = Result (Results.single (Result.foldr step init row))
-- ** Specialized multi-row results
2022-06-20 13:54:54 +03:00
-- |
-- Maybe one row or none.
{-# INLINEABLE rowMaybe #-}
2019-05-21 01:20:57 +03:00
rowMaybe :: Row a -> Result (Maybe a)
rowMaybe (Row row) = Result (Results.single (Result.maybe row))
2022-06-20 13:54:54 +03:00
-- |
-- Zero or more rows packed into the vector.
--
-- It's recommended to prefer this function to 'rowList',
-- since it performs notably better.
{-# INLINEABLE rowVector #-}
2019-05-21 01:20:57 +03:00
rowVector :: Row a -> Result (Vector a)
rowVector (Row row) = Result (Results.single (Result.vector row))
2022-06-20 13:54:54 +03:00
-- |
-- Zero or more rows packed into the list.
{-# INLINEABLE rowList #-}
2019-05-21 01:20:57 +03:00
rowList :: Row a -> Result [a]
rowList = foldrRows strictCons []
-- * Row
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of an individual row,
-- which gets composed of column value decoders.
--
-- E.g.:
--
-- @
-- x :: 'Row' (Maybe Int64, Text, TimeOfDay)
-- x = (,,) '<$>' ('column' . 'nullable') 'int8' '<*>' ('column' . 'nonNullable') 'text' '<*>' ('column' . 'nonNullable') 'time'
-- @
2019-05-21 13:18:20 +03:00
newtype Row a = Row (Row.Row a)
2020-05-09 18:12:42 +03:00
deriving (Functor, Applicative, Monad, MonadFail)
2019-05-21 01:20:57 +03:00
2022-06-20 13:54:54 +03:00
-- |
-- Lift an individual value decoder to a composable row decoder.
{-# INLINEABLE column #-}
2019-05-21 01:20:57 +03:00
column :: NullableOrNot Value a -> Row a
2022-06-20 13:54:54 +03:00
column = \case
2019-05-21 01:20:57 +03:00
NonNullable (Value imp) -> Row (Row.nonNullValue imp)
Nullable (Value imp) -> Row (Row.value imp)
-- * Nullability
2022-06-20 13:54:54 +03:00
-- |
-- Extensional specification of nullability over a generic decoder.
2019-05-21 01:20:57 +03:00
data NullableOrNot decoder a where
NonNullable :: decoder a -> NullableOrNot decoder a
Nullable :: decoder a -> NullableOrNot decoder (Maybe a)
2022-06-20 13:54:54 +03:00
-- |
-- Specify that a decoder produces a non-nullable value.
2019-05-21 01:20:57 +03:00
nonNullable :: decoder a -> NullableOrNot decoder a
nonNullable = NonNullable
2022-06-20 13:54:54 +03:00
-- |
-- Specify that a decoder produces a nullable value.
2019-05-21 01:20:57 +03:00
nullable :: decoder a -> NullableOrNot decoder (Maybe a)
nullable = Nullable
-- * Value
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of a value.
2019-05-21 01:20:57 +03:00
newtype Value a = Value (Value.Value a)
deriving (Functor)
type role Value representational
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @BOOL@ values.
{-# INLINEABLE bool #-}
2019-05-21 01:20:57 +03:00
bool :: Value Bool
bool = Value (Value.decoder (const A.bool))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @INT2@ values.
{-# INLINEABLE int2 #-}
2019-05-21 01:20:57 +03:00
int2 :: Value Int16
int2 = Value (Value.decoder (const A.int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @INT4@ values.
{-# INLINEABLE int4 #-}
2019-05-21 01:20:57 +03:00
int4 :: Value Int32
int4 = Value (Value.decoder (const A.int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @INT8@ values.
{-# INLINEABLE int8 #-}
2019-05-21 01:20:57 +03:00
int8 :: Value Int64
2022-06-20 13:54:54 +03:00
int8 =
{-# SCC "int8" #-}
2019-05-21 01:20:57 +03:00
Value (Value.decoder (const ({-# SCC "int8.int" #-} A.int)))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @FLOAT4@ values.
{-# INLINEABLE float4 #-}
2019-05-21 01:20:57 +03:00
float4 :: Value Float
float4 = Value (Value.decoder (const A.float4))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @FLOAT8@ values.
{-# INLINEABLE float8 #-}
2019-05-21 01:20:57 +03:00
float8 :: Value Double
float8 = Value (Value.decoder (const A.float8))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @NUMERIC@ values.
{-# INLINEABLE numeric #-}
numeric :: Value Scientific
2019-05-21 01:20:57 +03:00
numeric = Value (Value.decoder (const A.numeric))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @CHAR@ values.
-- Note that it supports Unicode values.
{-# INLINEABLE char #-}
2019-05-21 01:20:57 +03:00
char :: Value Char
char = Value (Value.decoder (const A.char))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @TEXT@ values.
{-# INLINEABLE text #-}
2019-05-21 01:20:57 +03:00
text :: Value Text
text = Value (Value.decoder (const A.text_strict))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @BYTEA@ values.
{-# INLINEABLE bytea #-}
2019-05-21 01:20:57 +03:00
bytea :: Value ByteString
bytea = Value (Value.decoder (const A.bytea_strict))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @DATE@ values.
{-# INLINEABLE date #-}
date :: Value Day
2019-05-21 01:20:57 +03:00
date = Value (Value.decoder (const A.date))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @TIMESTAMP@ values.
{-# INLINEABLE timestamp #-}
timestamp :: Value LocalTime
2019-05-21 01:20:57 +03:00
timestamp = Value (Value.decoder (Prelude.bool A.timestamp_float A.timestamp_int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @TIMESTAMPTZ@ values.
--
-- /NOTICE/
--
-- Postgres does not store the timezone information of @TIMESTAMPTZ@.
-- Instead it stores a UTC value and performs silent conversions
-- to the currently set timezone, when dealt with in the text format.
-- However this library bypasses the silent conversions
-- and communicates with Postgres using the UTC values directly.
{-# INLINEABLE timestamptz #-}
timestamptz :: Value UTCTime
2019-05-21 01:20:57 +03:00
timestamptz = Value (Value.decoder (Prelude.bool A.timestamptz_float A.timestamptz_int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @TIME@ values.
{-# INLINEABLE time #-}
time :: Value TimeOfDay
2019-05-21 01:20:57 +03:00
time = Value (Value.decoder (Prelude.bool A.time_float A.time_int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @TIMETZ@ values.
--
-- Unlike in case of @TIMESTAMPTZ@,
-- Postgres does store the timezone information for @TIMETZ@.
-- However the Haskell's \"time\" library does not contain any composite type,
-- that fits the task, so we use a pair of 'TimeOfDay' and 'TimeZone'
-- to represent a value on the Haskell's side.
{-# INLINEABLE timetz #-}
timetz :: Value (TimeOfDay, TimeZone)
2019-05-21 01:20:57 +03:00
timetz = Value (Value.decoder (Prelude.bool A.timetz_float A.timetz_int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @INTERVAL@ values.
{-# INLINEABLE interval #-}
interval :: Value DiffTime
2019-05-21 01:20:57 +03:00
interval = Value (Value.decoder (Prelude.bool A.interval_float A.interval_int))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @UUID@ values.
{-# INLINEABLE uuid #-}
uuid :: Value UUID
2019-05-21 01:20:57 +03:00
uuid = Value (Value.decoder (const A.uuid))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @INET@ values.
{-# INLINEABLE inet #-}
inet :: Value (NetworkIp.NetAddr NetworkIp.IP)
2019-05-21 01:20:57 +03:00
inet = Value (Value.decoder (const A.inet))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @JSON@ values into a JSON AST.
{-# INLINEABLE json #-}
json :: Value Aeson.Value
2019-05-21 01:20:57 +03:00
json = Value (Value.decoder (const A.json_ast))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @JSON@ values into a raw JSON 'ByteString'.
{-# INLINEABLE jsonBytes #-}
2019-05-21 01:20:57 +03:00
jsonBytes :: (ByteString -> Either Text a) -> Value a
jsonBytes fn = Value (Value.decoder (const (A.json_bytes fn)))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @JSONB@ values into a JSON AST.
{-# INLINEABLE jsonb #-}
jsonb :: Value Aeson.Value
2019-05-21 01:20:57 +03:00
jsonb = Value (Value.decoder (const A.jsonb_ast))
2022-06-20 13:54:54 +03:00
-- |
-- Decoder of the @JSONB@ values into a raw JSON 'ByteString'.
{-# INLINEABLE jsonbBytes #-}
2019-05-21 01:20:57 +03:00
jsonbBytes :: (ByteString -> Either Text a) -> Value a
jsonbBytes fn = Value (Value.decoder (const (A.jsonb_bytes fn)))
2022-06-20 13:54:54 +03:00
-- |
-- Lift a custom value decoder function to a 'Value' decoder.
{-# INLINEABLE custom #-}
2019-05-21 01:20:57 +03:00
custom :: (Bool -> ByteString -> Either Text a) -> Value a
custom fn = Value (Value.decoderFn fn)
2022-06-20 13:54:54 +03:00
-- |
-- Refine a value decoder, lifting the possible error to the session level.
{-# INLINEABLE refine #-}
2020-01-22 09:21:36 +03:00
refine :: (a -> Either Text b) -> Value a -> Value b
refine fn (Value v) = Value (Value.Value (\b -> A.refine fn (Value.run v b)))
2020-01-22 09:21:36 +03:00
2022-06-20 13:54:54 +03:00
-- |
-- A generic decoder of @HSTORE@ values.
--
-- Here's how you can use it to construct a specific value:
--
-- @
-- x :: Value [(Text, Maybe Text)]
-- x = hstore 'replicateM'
-- @
{-# INLINEABLE hstore #-}
2023-10-13 02:24:12 +03:00
hstore :: (forall m. (Monad m) => Int -> m (Text, Maybe Text) -> m a) -> Value a
2019-05-21 01:20:57 +03:00
hstore replicateM = Value (Value.decoder (const (A.hstore replicateM A.text_strict A.text_strict)))
2022-06-20 13:54:54 +03:00
-- |
-- Given a partial mapping from text to value,
-- produces a decoder of that value.
2019-05-21 01:20:57 +03:00
enum :: (Text -> Maybe a) -> Value a
enum mapping = Value (Value.decoder (const (A.enum mapping)))
2022-06-20 13:54:54 +03:00
-- |
-- Lift an 'Array' decoder to a 'Value' decoder.
{-# INLINEABLE array #-}
2019-05-21 01:20:57 +03:00
array :: Array a -> Value a
array (Array imp) = Value (Value.decoder (Array.run imp))
2022-06-20 13:54:54 +03:00
-- |
-- Lift a value decoder of element into a unidimensional array decoder producing a list.
--
-- This function is merely a shortcut to the following expression:
--
-- @
-- ('array' . 'dimension' Control.Monad.'replicateM' . 'element')
-- @
--
-- Please notice that in case of multidimensional arrays nesting 'listArray' decoder
-- won't work. You have to explicitly construct the array decoder using 'array'.
2019-05-21 21:34:20 +03:00
{-# INLINE listArray #-}
listArray :: NullableOrNot Value element -> Value [element]
listArray = array . dimension replicateM . element
2022-06-20 13:54:54 +03:00
-- |
-- Lift a value decoder of element into a unidimensional array decoder producing a generic vector.
--
-- This function is merely a shortcut to the following expression:
--
-- @
-- ('array' . 'dimension' Data.Vector.Generic.'GenericVector.replicateM' . 'element')
-- @
--
-- Please notice that in case of multidimensional arrays nesting 'vectorArray' decoder
-- won't work. You have to explicitly construct the array decoder using 'array'.
2019-05-21 21:34:20 +03:00
{-# INLINE vectorArray #-}
2023-10-13 02:24:12 +03:00
vectorArray :: (GenericVector.Vector vector element) => NullableOrNot Value element -> Value (vector element)
2019-05-21 21:34:20 +03:00
vectorArray = array . dimension GenericVector.replicateM . element
2022-06-20 13:54:54 +03:00
-- |
-- Lift a 'Composite' decoder to a 'Value' decoder.
{-# INLINEABLE composite #-}
2019-05-21 01:20:57 +03:00
composite :: Composite a -> Value a
composite (Composite imp) = Value (Value.decoder (Composite.run imp))
-- * Array decoders
2022-06-20 13:54:54 +03:00
-- |
-- A generic array decoder.
--
-- Here's how you can use it to produce a specific array value decoder:
--
-- @
-- x :: 'Value' [[Text]]
-- x = 'array' ('dimension' 'replicateM' ('dimension' 'replicateM' ('element' ('nonNullable' 'text'))))
-- @
2019-05-21 01:20:57 +03:00
newtype Array a = Array (Array.Array a)
deriving (Functor)
2022-06-20 13:54:54 +03:00
-- |
-- A function for parsing a dimension of an array.
-- Provides support for multi-dimensional arrays.
--
-- Accepts:
--
-- * An implementation of the @replicateM@ function
-- (@Control.Monad.'Control.Monad.replicateM'@, @Data.Vector.'Data.Vector.replicateM'@),
-- which determines the output value.
--
-- * A decoder of its components, which can be either another 'dimension' or 'element'.
{-# INLINEABLE dimension #-}
2023-10-13 02:24:12 +03:00
dimension :: (forall m. (Monad m) => Int -> m a -> m b) -> Array a -> Array b
2019-05-21 01:20:57 +03:00
dimension replicateM (Array imp) = Array (Array.dimension replicateM imp)
2022-06-20 13:54:54 +03:00
-- |
-- Lift a 'Value' decoder into an 'Array' decoder for parsing of leaf values.
{-# INLINEABLE element #-}
2019-05-21 01:20:57 +03:00
element :: NullableOrNot Value a -> Array a
2022-06-20 13:54:54 +03:00
element = \case
2019-05-21 01:20:57 +03:00
NonNullable (Value imp) -> Array (Array.nonNullValue (Value.run imp))
Nullable (Value imp) -> Array (Array.value (Value.run imp))
-- * Composite decoders
2022-06-20 13:54:54 +03:00
-- |
-- Composable decoder of composite values (rows, records).
2019-05-21 01:20:57 +03:00
newtype Composite a = Composite (Composite.Composite a)
2020-06-13 13:33:02 +03:00
deriving (Functor, Applicative, Monad, MonadFail)
2019-05-21 01:20:57 +03:00
2022-06-20 13:54:54 +03:00
-- |
-- Lift a 'Value' decoder into a 'Composite' decoder for parsing of component values.
2019-05-21 01:20:57 +03:00
field :: NullableOrNot Value a -> Composite a
2022-06-20 13:54:54 +03:00
field = \case
2019-05-21 01:20:57 +03:00
NonNullable (Value imp) -> Composite (Composite.nonNullValue (Value.run imp))
Nullable (Value imp) -> Composite (Composite.value (Value.run imp))