2015-11-08 21:09:42 +03:00
|
|
|
-- |
|
2015-11-21 16:42:12 +03:00
|
|
|
-- A DSL for declaration of result decoders.
|
2015-12-05 09:09:31 +03:00
|
|
|
module Hasql.Decoders
|
2015-11-08 21:09:42 +03:00
|
|
|
(
|
|
|
|
-- * Result
|
|
|
|
Result,
|
2015-11-22 08:34:27 +03:00
|
|
|
unit,
|
2015-11-08 21:09:42 +03:00
|
|
|
rowsAffected,
|
|
|
|
singleRow,
|
|
|
|
-- ** Specialized multi-row results
|
2018-05-23 13:11:16 +03:00
|
|
|
rowMaybe,
|
|
|
|
rowVector,
|
|
|
|
rowList,
|
2015-11-08 21:09:42 +03:00
|
|
|
-- ** Multi-row traversers
|
|
|
|
foldlRows,
|
|
|
|
foldrRows,
|
|
|
|
-- * Row
|
|
|
|
Row,
|
2018-05-23 13:04:13 +03:00
|
|
|
column,
|
|
|
|
nullableColumn,
|
2015-11-08 21:09:42 +03:00
|
|
|
-- * Value
|
|
|
|
Value,
|
|
|
|
bool,
|
|
|
|
int2,
|
|
|
|
int4,
|
|
|
|
int8,
|
|
|
|
float4,
|
|
|
|
float8,
|
|
|
|
numeric,
|
|
|
|
char,
|
|
|
|
text,
|
|
|
|
bytea,
|
|
|
|
date,
|
|
|
|
timestamp,
|
|
|
|
timestamptz,
|
|
|
|
time,
|
|
|
|
timetz,
|
|
|
|
interval,
|
|
|
|
uuid,
|
2017-03-14 18:11:42 +03:00
|
|
|
inet,
|
2015-11-08 21:09:42 +03:00
|
|
|
json,
|
2016-02-09 13:14:19 +03:00
|
|
|
jsonBytes,
|
2016-01-29 11:46:18 +03:00
|
|
|
jsonb,
|
2016-02-09 13:14:19 +03:00
|
|
|
jsonbBytes,
|
2015-11-08 21:09:42 +03:00
|
|
|
array,
|
|
|
|
composite,
|
|
|
|
hstore,
|
2015-11-10 17:53:14 +03:00
|
|
|
enum,
|
2016-01-28 14:13:09 +03:00
|
|
|
custom,
|
2015-11-08 21:09:42 +03:00
|
|
|
-- * Array
|
|
|
|
Array,
|
2018-05-23 13:04:13 +03:00
|
|
|
dimension,
|
|
|
|
element,
|
|
|
|
nullableElement,
|
2015-11-08 21:09:42 +03:00
|
|
|
-- * Composite
|
|
|
|
Composite,
|
2018-05-23 13:04:13 +03:00
|
|
|
field,
|
|
|
|
nullableField,
|
2015-11-08 21:09:42 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2016-08-06 12:22:11 +03:00
|
|
|
import Hasql.Private.Prelude hiding (maybe, bool)
|
2015-11-08 21:09:42 +03:00
|
|
|
import qualified Data.Vector as Vector
|
2017-03-20 23:13:21 +03:00
|
|
|
import qualified PostgreSQL.Binary.Decoding as A
|
|
|
|
import qualified PostgreSQL.Binary.Data as B
|
2016-08-06 12:22:11 +03:00
|
|
|
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
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- * Result
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2015-11-21 13:36:01 +03:00
|
|
|
-- Decoder of a query result.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
newtype Result a =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.Results a)
|
2015-11-08 21:09:42 +03:00
|
|
|
deriving (Functor)
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decode no column from the result.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- Useful for statements like @INSERT@ or @CREATE@.
|
|
|
|
--
|
2015-11-22 08:34:27 +03:00
|
|
|
{-# INLINABLE unit #-}
|
|
|
|
unit :: Result ()
|
|
|
|
unit =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single Result.unit)
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Get the amount of rows affected by such statements as
|
|
|
|
-- @UPDATE@ or @DELETE@.
|
|
|
|
--
|
|
|
|
{-# INLINABLE rowsAffected #-}
|
|
|
|
rowsAffected :: Result Int64
|
|
|
|
rowsAffected =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single Result.rowsAffected)
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Exactly one row.
|
2018-05-23 13:33:01 +03:00
|
|
|
-- Will raise the 'Hasql.Errors.UnexpectedAmountOfRows' error if it's any other.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE singleRow #-}
|
|
|
|
singleRow :: Row a -> Result a
|
|
|
|
singleRow (Row row) =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single (Result.single row))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- ** Multi-row traversers
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Foldl multiple rows.
|
|
|
|
--
|
|
|
|
{-# INLINABLE foldlRows #-}
|
|
|
|
foldlRows :: (a -> b -> a) -> a -> Row b -> Result a
|
|
|
|
foldlRows step init (Row row) =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single (Result.foldl step init row))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Foldr multiple rows.
|
|
|
|
--
|
|
|
|
{-# INLINABLE foldrRows #-}
|
|
|
|
foldrRows :: (b -> a -> a) -> a -> Row b -> Result a
|
|
|
|
foldrRows step init (Row row) =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single (Result.foldr step init row))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- ** Specialized multi-row results
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maybe one row or none.
|
|
|
|
--
|
2018-05-23 13:11:16 +03:00
|
|
|
{-# INLINABLE rowMaybe #-}
|
|
|
|
rowMaybe :: Row a -> Result (Maybe a)
|
|
|
|
rowMaybe (Row row) =
|
2015-11-16 20:13:15 +03:00
|
|
|
Result (Results.single (Result.maybe row))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Zero or more rows packed into the vector.
|
|
|
|
--
|
2018-05-23 13:11:16 +03:00
|
|
|
-- It's recommended to prefer this function to 'rowList',
|
2015-11-21 16:41:13 +03:00
|
|
|
-- since it performs notably better.
|
2015-11-21 13:18:55 +03:00
|
|
|
--
|
2018-05-23 13:11:16 +03:00
|
|
|
{-# INLINABLE rowVector #-}
|
|
|
|
rowVector :: Row a -> Result (Vector a)
|
|
|
|
rowVector (Row row) =
|
2015-11-21 13:10:29 +03:00
|
|
|
Result (Results.single (Result.vector row))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Zero or more rows packed into the list.
|
|
|
|
--
|
2018-05-23 13:11:16 +03:00
|
|
|
{-# INLINABLE rowList #-}
|
|
|
|
rowList :: Row a -> Result [a]
|
|
|
|
rowList =
|
2015-11-21 09:57:44 +03:00
|
|
|
foldrRows strictCons []
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
|
|
|
|
-- ** Instances
|
|
|
|
-------------------------
|
|
|
|
|
2015-11-22 08:34:27 +03:00
|
|
|
-- | Maps to 'unit'.
|
2015-11-08 21:09:42 +03:00
|
|
|
instance Default (Result ()) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2015-11-22 08:34:27 +03:00
|
|
|
unit
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- | Maps to 'rowsAffected'.
|
|
|
|
instance Default (Result Int64) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
rowsAffected
|
|
|
|
|
2018-05-23 13:11:16 +03:00
|
|
|
-- | Maps to @('rowMaybe' def)@.
|
2015-11-08 21:09:42 +03:00
|
|
|
instance Default (Row a) => Default (Result (Maybe a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:11:16 +03:00
|
|
|
rowMaybe def
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2018-05-23 13:11:16 +03:00
|
|
|
-- | Maps to @('rowVector' def)@.
|
2015-11-08 21:09:42 +03:00
|
|
|
instance Default (Row a) => Default (Result (Vector a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:11:16 +03:00
|
|
|
rowVector def
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2018-05-23 13:11:16 +03:00
|
|
|
-- | Maps to @('rowList' def)@.
|
2015-11-08 21:09:42 +03:00
|
|
|
instance Default (Row a) => Default (Result ([] a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:11:16 +03:00
|
|
|
rowList def
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- | Maps to @(fmap Identity ('singleRow' def)@.
|
|
|
|
instance Default (Row a) => Default (Result (Identity a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
fmap Identity (singleRow def)
|
|
|
|
|
|
|
|
|
|
|
|
-- * Row
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2015-11-21 13:36:01 +03:00
|
|
|
-- Decoder of an individual row,
|
2018-05-23 13:04:13 +03:00
|
|
|
-- which gets composed of column column decoders.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- E.g.:
|
|
|
|
--
|
|
|
|
-- >x :: Row (Maybe Int64, Text, TimeOfDay)
|
|
|
|
-- >x =
|
2018-05-23 13:04:13 +03:00
|
|
|
-- > (,,) <$> nullableColumn int8 <*> column text <*> column time
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
newtype Row a =
|
|
|
|
Row (Row.Row a)
|
|
|
|
deriving (Functor, Applicative, Monad)
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift an individual non-nullable column decoder to a composable row decoder.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
{-# INLINABLE column #-}
|
|
|
|
column :: Value a -> Row a
|
|
|
|
column (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Row (Row.nonNullValue imp)
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift an individual nullable column decoder to a composable row decoder.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
{-# INLINABLE nullableColumn #-}
|
|
|
|
nullableColumn :: Value a -> Row (Maybe a)
|
|
|
|
nullableColumn (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Row (Row.value imp)
|
|
|
|
|
|
|
|
|
|
|
|
-- ** Instances
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
instance Default (Value a) => Default (Row (Identity a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:04:13 +03:00
|
|
|
fmap Identity (column def)
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
instance Default (Value a) => Default (Row (Maybe a)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:04:13 +03:00
|
|
|
nullableColumn def
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
instance (Default (Value a1), Default (Value a2)) => Default (Row (a1, a2)) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
2018-05-23 13:04:13 +03:00
|
|
|
ap (fmap (,) (column def)) (column def)
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
|
|
|
|
-- * Value
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of an individual column.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
newtype Value a =
|
|
|
|
Value (Value.Value a)
|
|
|
|
deriving (Functor)
|
|
|
|
|
|
|
|
|
2018-05-23 13:04:13 +03:00
|
|
|
-- ** Plain column decoders
|
2015-11-08 21:09:42 +03:00
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @BOOL@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE bool #-}
|
|
|
|
bool :: Value Bool
|
|
|
|
bool =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.bool))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @INT2@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE int2 #-}
|
|
|
|
int2 :: Value Int16
|
|
|
|
int2 =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @INT4@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE int4 #-}
|
|
|
|
int4 :: Value Int32
|
|
|
|
int4 =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @INT8@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE int8 #-}
|
|
|
|
int8 :: Value Int64
|
|
|
|
int8 =
|
2015-11-20 09:28:26 +03:00
|
|
|
{-# SCC "int8" #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const ({-# SCC "int8.int" #-} A.int)))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @FLOAT4@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE float4 #-}
|
|
|
|
float4 :: Value Float
|
|
|
|
float4 =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.float4))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @FLOAT8@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE float8 #-}
|
|
|
|
float8 :: Value Double
|
|
|
|
float8 =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.float8))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @NUMERIC@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE numeric #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
numeric :: Value B.Scientific
|
2015-11-08 21:09:42 +03:00
|
|
|
numeric =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.numeric))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @CHAR@ columns.
|
|
|
|
-- Note that it supports UTF-8 columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINABLE char #-}
|
|
|
|
char :: Value Char
|
|
|
|
char =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.char))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @TEXT@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE text #-}
|
|
|
|
text :: Value Text
|
|
|
|
text =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.text_strict))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @BYTEA@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE bytea #-}
|
|
|
|
bytea :: Value ByteString
|
|
|
|
bytea =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.bytea_strict))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @DATE@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE date #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
date :: Value B.Day
|
2015-11-08 21:09:42 +03:00
|
|
|
date =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.date))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @TIMESTAMP@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE timestamp #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
timestamp :: Value B.LocalTime
|
2015-11-08 21:09:42 +03:00
|
|
|
timestamp =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (Prelude.bool A.timestamp_float A.timestamp_int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @TIMESTAMPTZ@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- /NOTICE/
|
|
|
|
--
|
|
|
|
-- Postgres does not store the timezone information of @TIMESTAMPTZ@.
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Instead it stores a UTC column and performs silent conversions
|
2015-11-08 21:09:42 +03:00
|
|
|
-- to the currently set timezone, when dealt with in the text format.
|
|
|
|
-- However this library bypasses the silent conversions
|
2018-05-23 13:04:13 +03:00
|
|
|
-- and communicates with Postgres using the UTC columns directly.
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINABLE timestamptz #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
timestamptz :: Value B.UTCTime
|
2015-11-08 21:09:42 +03:00
|
|
|
timestamptz =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (Prelude.bool A.timestamptz_float A.timestamptz_int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @TIME@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE time #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
time :: Value B.TimeOfDay
|
2015-11-08 21:09:42 +03:00
|
|
|
time =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (Prelude.bool A.time_float A.time_int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @TIMETZ@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- 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'
|
2018-05-23 13:04:13 +03:00
|
|
|
-- to represent a column on the Haskell's side.
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINABLE timetz #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
timetz :: Value (B.TimeOfDay, B.TimeZone)
|
2015-11-08 21:09:42 +03:00
|
|
|
timetz =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (Prelude.bool A.timetz_float A.timetz_int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @INTERVAL@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE interval #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
interval :: Value B.DiffTime
|
2015-11-08 21:09:42 +03:00
|
|
|
interval =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (Prelude.bool A.interval_float A.interval_int))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @UUID@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE uuid #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
uuid :: Value B.UUID
|
2015-11-08 21:09:42 +03:00
|
|
|
uuid =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.uuid))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2017-03-14 18:11:42 +03:00
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @INET@ columns.
|
2017-03-14 18:11:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE inet #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
inet :: Value (B.NetAddr B.IP)
|
2017-03-14 18:11:42 +03:00
|
|
|
inet =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.inet))
|
2017-03-14 18:11:42 +03:00
|
|
|
|
2015-11-08 21:09:42 +03:00
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @JSON@ columns into a JSON AST.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE json #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
json :: Value B.Value
|
2015-11-08 21:09:42 +03:00
|
|
|
json =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.json_ast))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2016-01-29 11:46:18 +03:00
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @JSON@ columns into a raw JSON 'ByteString'.
|
2016-02-09 13:14:19 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE jsonBytes #-}
|
|
|
|
jsonBytes :: (ByteString -> Either Text a) -> Value a
|
|
|
|
jsonBytes fn =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const (A.json_bytes fn)))
|
2016-02-09 13:14:19 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @JSONB@ columns into a JSON AST.
|
2016-01-29 11:46:18 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE jsonb #-}
|
2017-03-20 23:13:21 +03:00
|
|
|
jsonb :: Value B.Value
|
2016-01-29 11:46:18 +03:00
|
|
|
jsonb =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const A.jsonb_ast))
|
2016-02-09 13:14:19 +03:00
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Decoder of the @JSONB@ columns into a raw JSON 'ByteString'.
|
2016-02-09 13:14:19 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE jsonbBytes #-}
|
|
|
|
jsonbBytes :: (ByteString -> Either Text a) -> Value a
|
|
|
|
jsonbBytes fn =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const (A.jsonb_bytes fn)))
|
2016-01-29 11:46:18 +03:00
|
|
|
|
2016-01-28 14:13:09 +03:00
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lifts a custom column decoder function to a 'Value' decoder.
|
2016-01-28 14:13:09 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE custom #-}
|
|
|
|
custom :: (Bool -> ByteString -> Either Text a) -> Value a
|
|
|
|
custom fn =
|
|
|
|
Value (Value.decoderFn fn)
|
|
|
|
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2018-05-23 13:04:13 +03:00
|
|
|
-- ** Composite column decoders
|
2015-11-08 21:09:42 +03:00
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2015-11-21 13:36:01 +03:00
|
|
|
-- Lifts the 'Array' decoder to the 'Value' decoder.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE array #-}
|
|
|
|
array :: Array a -> Value a
|
|
|
|
array (Array imp) =
|
|
|
|
Value (Value.decoder (Array.run imp))
|
|
|
|
|
|
|
|
-- |
|
2015-11-21 13:36:01 +03:00
|
|
|
-- Lifts the 'Composite' decoder to the 'Value' decoder.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
{-# INLINABLE composite #-}
|
|
|
|
composite :: Composite a -> Value a
|
|
|
|
composite (Composite imp) =
|
|
|
|
Value (Value.decoder (Composite.run imp))
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- A generic decoder of @HSTORE@ columns.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Here's how you can use it to construct a specific column:
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- x :: Value [(Text, Maybe Text)]
|
|
|
|
-- x =
|
|
|
|
-- hstore 'replicateM'
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
{-# INLINABLE hstore #-}
|
|
|
|
hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a
|
|
|
|
hstore replicateM =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const (A.hstore replicateM A.text_strict A.text_strict)))
|
2015-11-08 21:09:42 +03:00
|
|
|
|
2015-11-10 17:53:14 +03:00
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Given a partial mapping from text to column,
|
|
|
|
-- produces a decoder of that column.
|
2015-11-10 17:53:14 +03:00
|
|
|
enum :: (Text -> Maybe a) -> Value a
|
|
|
|
enum mapping =
|
2017-03-20 23:13:21 +03:00
|
|
|
Value (Value.decoder (const (A.enum mapping)))
|
2015-11-10 17:53:14 +03:00
|
|
|
|
2015-11-08 21:09:42 +03:00
|
|
|
|
|
|
|
-- ** Instances
|
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'bool'.
|
|
|
|
instance Default (Value Bool) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
bool
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'int2'.
|
|
|
|
instance Default (Value Int16) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
int2
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'int4'.
|
|
|
|
instance Default (Value Int32) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
int4
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'int8'.
|
|
|
|
instance Default (Value Int64) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
int8
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'float4'.
|
|
|
|
instance Default (Value Float) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
float4
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'float8'.
|
|
|
|
instance Default (Value Double) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
float8
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'numeric'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.Scientific) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
numeric
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'char'.
|
|
|
|
instance Default (Value Char) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
char
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'text'.
|
|
|
|
instance Default (Value Text) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
text
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'bytea'.
|
|
|
|
instance Default (Value ByteString) where
|
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
bytea
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'date'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.Day) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
date
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'timestamp'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.LocalTime) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
timestamp
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'timestamptz'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.UTCTime) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
timestamptz
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'time'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.TimeOfDay) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
time
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'timetz'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value (B.TimeOfDay, B.TimeZone)) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
timetz
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'interval'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.DiffTime) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
interval
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'uuid'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.UUID) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
uuid
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- Maps to 'json'.
|
2017-03-20 23:13:21 +03:00
|
|
|
instance Default (Value B.Value) where
|
2015-11-08 21:09:42 +03:00
|
|
|
{-# INLINE def #-}
|
|
|
|
def =
|
|
|
|
json
|
|
|
|
|
|
|
|
|
2015-11-21 13:36:01 +03:00
|
|
|
-- * Array decoders
|
2015-11-08 21:09:42 +03:00
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2015-11-21 13:36:01 +03:00
|
|
|
-- A generic array decoder.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Here's how you can use it to produce a specific array column decoder:
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- x :: Value [[Text]]
|
|
|
|
-- x =
|
2018-05-23 13:04:13 +03:00
|
|
|
-- array (dimension 'replicateM' (dimension 'replicateM' (element text)))
|
2015-11-08 21:09:42 +03:00
|
|
|
-- @
|
|
|
|
--
|
|
|
|
newtype Array a =
|
|
|
|
Array (Array.Array a)
|
|
|
|
deriving (Functor)
|
|
|
|
|
|
|
|
-- |
|
|
|
|
-- 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'@),
|
2018-05-23 13:04:13 +03:00
|
|
|
-- which determines the output column.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
-- * A decoder of its components, which can be either another 'dimension',
|
|
|
|
-- 'element' or 'nullableElement'.
|
2015-11-08 21:09:42 +03:00
|
|
|
--
|
2018-05-23 13:04:13 +03:00
|
|
|
{-# INLINABLE dimension #-}
|
|
|
|
dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
|
|
|
|
dimension replicateM (Array imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Array (Array.dimension replicateM imp)
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift a 'Value' decoder into an 'Array' decoder for parsing of non-nullable leaf columns.
|
|
|
|
{-# INLINABLE element #-}
|
|
|
|
element :: Value a -> Array a
|
|
|
|
element (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Array (Array.nonNullValue (Value.run imp))
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift a 'Value' decoder into an 'Array' decoder for parsing of nullable leaf columns.
|
|
|
|
{-# INLINABLE nullableElement #-}
|
|
|
|
nullableElement :: Value a -> Array (Maybe a)
|
|
|
|
nullableElement (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Array (Array.value (Value.run imp))
|
|
|
|
|
|
|
|
|
2015-11-21 13:36:01 +03:00
|
|
|
-- * Composite decoders
|
2015-11-08 21:09:42 +03:00
|
|
|
-------------------------
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Composable decoder of composite columns (rows, records).
|
2015-11-08 21:09:42 +03:00
|
|
|
newtype Composite a =
|
|
|
|
Composite (Composite.Composite a)
|
|
|
|
deriving (Functor, Applicative, Monad)
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift a 'Value' decoder into a 'Composite' decoder for parsing of non-nullable leaf columns.
|
|
|
|
{-# INLINABLE field #-}
|
|
|
|
field :: Value a -> Composite a
|
|
|
|
field (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Composite (Composite.nonNullValue (Value.run imp))
|
|
|
|
|
|
|
|
-- |
|
2018-05-23 13:04:13 +03:00
|
|
|
-- Lift a 'Value' decoder into a 'Composite' decoder for parsing of nullable leaf columns.
|
|
|
|
{-# INLINABLE nullableField #-}
|
|
|
|
nullableField :: Value a -> Composite (Maybe a)
|
|
|
|
nullableField (Value imp) =
|
2015-11-08 21:09:42 +03:00
|
|
|
Composite (Composite.value (Value.run imp))
|
|
|
|
|