mirror of
https://github.com/nikita-volkov/hasql.git
synced 2024-12-25 11:11:36 +03:00
Make the codec names more consistent
This commit is contained in:
parent
ea4874ca7e
commit
8eb3830a7f
@ -79,7 +79,7 @@ queryWithSingleRow =
|
||||
D.singleRow row
|
||||
where
|
||||
row =
|
||||
tuple <$> D.value D.int8 <*> D.value D.int8
|
||||
tuple <$> D.column D.int8 <*> D.column D.int8
|
||||
where
|
||||
tuple !a !b =
|
||||
(a, b)
|
||||
@ -93,7 +93,7 @@ queryWithManyRows decoder =
|
||||
encoder =
|
||||
conquer
|
||||
rowDecoder =
|
||||
tuple <$> D.value D.int8 <*> D.value D.int8
|
||||
tuple <$> D.column D.int8 <*> D.column D.int8
|
||||
where
|
||||
tuple !a !b =
|
||||
(a, b)
|
||||
|
@ -16,8 +16,8 @@ module Hasql.Decoders
|
||||
foldrRows,
|
||||
-- * Row
|
||||
Row,
|
||||
value,
|
||||
nullableValue,
|
||||
column,
|
||||
nullableColumn,
|
||||
-- * Value
|
||||
Value,
|
||||
bool,
|
||||
@ -49,13 +49,13 @@ module Hasql.Decoders
|
||||
custom,
|
||||
-- * Array
|
||||
Array,
|
||||
arrayDimension,
|
||||
arrayValue,
|
||||
arrayNullableValue,
|
||||
dimension,
|
||||
element,
|
||||
nullableElement,
|
||||
-- * Composite
|
||||
Composite,
|
||||
compositeValue,
|
||||
compositeNullableValue,
|
||||
field,
|
||||
nullableField,
|
||||
)
|
||||
where
|
||||
|
||||
@ -82,7 +82,7 @@ newtype Result a =
|
||||
deriving (Functor)
|
||||
|
||||
-- |
|
||||
-- Decode no value from the result.
|
||||
-- Decode no column from the result.
|
||||
--
|
||||
-- Useful for statements like @INSERT@ or @CREATE@.
|
||||
--
|
||||
@ -204,32 +204,32 @@ instance Default (Row a) => Default (Result (Identity a)) where
|
||||
|
||||
-- |
|
||||
-- Decoder of an individual row,
|
||||
-- which gets composed of column value decoders.
|
||||
-- which gets composed of column column decoders.
|
||||
--
|
||||
-- E.g.:
|
||||
--
|
||||
-- >x :: Row (Maybe Int64, Text, TimeOfDay)
|
||||
-- >x =
|
||||
-- > (,,) <$> nullableValue int8 <*> value text <*> value time
|
||||
-- > (,,) <$> nullableColumn int8 <*> column text <*> column time
|
||||
--
|
||||
newtype Row a =
|
||||
Row (Row.Row a)
|
||||
deriving (Functor, Applicative, Monad)
|
||||
|
||||
-- |
|
||||
-- Lift an individual non-nullable value decoder to a composable row decoder.
|
||||
-- Lift an individual non-nullable column decoder to a composable row decoder.
|
||||
--
|
||||
{-# INLINABLE value #-}
|
||||
value :: Value a -> Row a
|
||||
value (Value imp) =
|
||||
{-# INLINABLE column #-}
|
||||
column :: Value a -> Row a
|
||||
column (Value imp) =
|
||||
Row (Row.nonNullValue imp)
|
||||
|
||||
-- |
|
||||
-- Lift an individual nullable value decoder to a composable row decoder.
|
||||
-- Lift an individual nullable column decoder to a composable row decoder.
|
||||
--
|
||||
{-# INLINABLE nullableValue #-}
|
||||
nullableValue :: Value a -> Row (Maybe a)
|
||||
nullableValue (Value imp) =
|
||||
{-# INLINABLE nullableColumn #-}
|
||||
nullableColumn :: Value a -> Row (Maybe a)
|
||||
nullableColumn (Value imp) =
|
||||
Row (Row.value imp)
|
||||
|
||||
|
||||
@ -239,35 +239,35 @@ nullableValue (Value imp) =
|
||||
instance Default (Value a) => Default (Row (Identity a)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
fmap Identity (value def)
|
||||
fmap Identity (column def)
|
||||
|
||||
instance Default (Value a) => Default (Row (Maybe a)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
nullableValue def
|
||||
nullableColumn def
|
||||
|
||||
instance (Default (Value a1), Default (Value a2)) => Default (Row (a1, a2)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
ap (fmap (,) (value def)) (value def)
|
||||
ap (fmap (,) (column def)) (column def)
|
||||
|
||||
|
||||
-- * Value
|
||||
-------------------------
|
||||
|
||||
-- |
|
||||
-- Decoder of an individual value.
|
||||
-- Decoder of an individual column.
|
||||
--
|
||||
newtype Value a =
|
||||
Value (Value.Value a)
|
||||
deriving (Functor)
|
||||
|
||||
|
||||
-- ** Plain value decoders
|
||||
-- ** Plain column decoders
|
||||
-------------------------
|
||||
|
||||
-- |
|
||||
-- Decoder of the @BOOL@ values.
|
||||
-- Decoder of the @BOOL@ columns.
|
||||
--
|
||||
{-# INLINABLE bool #-}
|
||||
bool :: Value Bool
|
||||
@ -275,7 +275,7 @@ bool =
|
||||
Value (Value.decoder (const A.bool))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @INT2@ values.
|
||||
-- Decoder of the @INT2@ columns.
|
||||
--
|
||||
{-# INLINABLE int2 #-}
|
||||
int2 :: Value Int16
|
||||
@ -283,7 +283,7 @@ int2 =
|
||||
Value (Value.decoder (const A.int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @INT4@ values.
|
||||
-- Decoder of the @INT4@ columns.
|
||||
--
|
||||
{-# INLINABLE int4 #-}
|
||||
int4 :: Value Int32
|
||||
@ -291,7 +291,7 @@ int4 =
|
||||
Value (Value.decoder (const A.int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @INT8@ values.
|
||||
-- Decoder of the @INT8@ columns.
|
||||
--
|
||||
{-# INLINABLE int8 #-}
|
||||
int8 :: Value Int64
|
||||
@ -300,7 +300,7 @@ int8 =
|
||||
Value (Value.decoder (const ({-# SCC "int8.int" #-} A.int)))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @FLOAT4@ values.
|
||||
-- Decoder of the @FLOAT4@ columns.
|
||||
--
|
||||
{-# INLINABLE float4 #-}
|
||||
float4 :: Value Float
|
||||
@ -308,7 +308,7 @@ float4 =
|
||||
Value (Value.decoder (const A.float4))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @FLOAT8@ values.
|
||||
-- Decoder of the @FLOAT8@ columns.
|
||||
--
|
||||
{-# INLINABLE float8 #-}
|
||||
float8 :: Value Double
|
||||
@ -316,7 +316,7 @@ float8 =
|
||||
Value (Value.decoder (const A.float8))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @NUMERIC@ values.
|
||||
-- Decoder of the @NUMERIC@ columns.
|
||||
--
|
||||
{-# INLINABLE numeric #-}
|
||||
numeric :: Value B.Scientific
|
||||
@ -324,15 +324,15 @@ numeric =
|
||||
Value (Value.decoder (const A.numeric))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @CHAR@ values.
|
||||
-- Note that it supports UTF-8 values.
|
||||
-- Decoder of the @CHAR@ columns.
|
||||
-- Note that it supports UTF-8 columns.
|
||||
{-# INLINABLE char #-}
|
||||
char :: Value Char
|
||||
char =
|
||||
Value (Value.decoder (const A.char))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @TEXT@ values.
|
||||
-- Decoder of the @TEXT@ columns.
|
||||
--
|
||||
{-# INLINABLE text #-}
|
||||
text :: Value Text
|
||||
@ -340,7 +340,7 @@ text =
|
||||
Value (Value.decoder (const A.text_strict))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @BYTEA@ values.
|
||||
-- Decoder of the @BYTEA@ columns.
|
||||
--
|
||||
{-# INLINABLE bytea #-}
|
||||
bytea :: Value ByteString
|
||||
@ -348,7 +348,7 @@ bytea =
|
||||
Value (Value.decoder (const A.bytea_strict))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @DATE@ values.
|
||||
-- Decoder of the @DATE@ columns.
|
||||
--
|
||||
{-# INLINABLE date #-}
|
||||
date :: Value B.Day
|
||||
@ -356,7 +356,7 @@ date =
|
||||
Value (Value.decoder (const A.date))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @TIMESTAMP@ values.
|
||||
-- Decoder of the @TIMESTAMP@ columns.
|
||||
--
|
||||
{-# INLINABLE timestamp #-}
|
||||
timestamp :: Value B.LocalTime
|
||||
@ -364,22 +364,22 @@ timestamp =
|
||||
Value (Value.decoder (Prelude.bool A.timestamp_float A.timestamp_int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @TIMESTAMPTZ@ values.
|
||||
-- Decoder of the @TIMESTAMPTZ@ columns.
|
||||
--
|
||||
-- /NOTICE/
|
||||
--
|
||||
-- Postgres does not store the timezone information of @TIMESTAMPTZ@.
|
||||
-- Instead it stores a UTC value and performs silent conversions
|
||||
-- Instead it stores a UTC column 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.
|
||||
-- and communicates with Postgres using the UTC columns directly.
|
||||
{-# INLINABLE timestamptz #-}
|
||||
timestamptz :: Value B.UTCTime
|
||||
timestamptz =
|
||||
Value (Value.decoder (Prelude.bool A.timestamptz_float A.timestamptz_int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @TIME@ values.
|
||||
-- Decoder of the @TIME@ columns.
|
||||
--
|
||||
{-# INLINABLE time #-}
|
||||
time :: Value B.TimeOfDay
|
||||
@ -387,20 +387,20 @@ time =
|
||||
Value (Value.decoder (Prelude.bool A.time_float A.time_int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @TIMETZ@ values.
|
||||
-- Decoder of the @TIMETZ@ columns.
|
||||
--
|
||||
-- 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.
|
||||
-- to represent a column on the Haskell's side.
|
||||
{-# INLINABLE timetz #-}
|
||||
timetz :: Value (B.TimeOfDay, B.TimeZone)
|
||||
timetz =
|
||||
Value (Value.decoder (Prelude.bool A.timetz_float A.timetz_int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @INTERVAL@ values.
|
||||
-- Decoder of the @INTERVAL@ columns.
|
||||
--
|
||||
{-# INLINABLE interval #-}
|
||||
interval :: Value B.DiffTime
|
||||
@ -408,7 +408,7 @@ interval =
|
||||
Value (Value.decoder (Prelude.bool A.interval_float A.interval_int))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @UUID@ values.
|
||||
-- Decoder of the @UUID@ columns.
|
||||
--
|
||||
{-# INLINABLE uuid #-}
|
||||
uuid :: Value B.UUID
|
||||
@ -416,7 +416,7 @@ uuid =
|
||||
Value (Value.decoder (const A.uuid))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @INET@ values.
|
||||
-- Decoder of the @INET@ columns.
|
||||
--
|
||||
{-# INLINABLE inet #-}
|
||||
inet :: Value (B.NetAddr B.IP)
|
||||
@ -424,7 +424,7 @@ inet =
|
||||
Value (Value.decoder (const A.inet))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @JSON@ values into a JSON AST.
|
||||
-- Decoder of the @JSON@ columns into a JSON AST.
|
||||
--
|
||||
{-# INLINABLE json #-}
|
||||
json :: Value B.Value
|
||||
@ -432,7 +432,7 @@ json =
|
||||
Value (Value.decoder (const A.json_ast))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @JSON@ values into a raw JSON 'ByteString'.
|
||||
-- Decoder of the @JSON@ columns into a raw JSON 'ByteString'.
|
||||
--
|
||||
{-# INLINABLE jsonBytes #-}
|
||||
jsonBytes :: (ByteString -> Either Text a) -> Value a
|
||||
@ -440,7 +440,7 @@ jsonBytes fn =
|
||||
Value (Value.decoder (const (A.json_bytes fn)))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @JSONB@ values into a JSON AST.
|
||||
-- Decoder of the @JSONB@ columns into a JSON AST.
|
||||
--
|
||||
{-# INLINABLE jsonb #-}
|
||||
jsonb :: Value B.Value
|
||||
@ -448,7 +448,7 @@ jsonb =
|
||||
Value (Value.decoder (const A.jsonb_ast))
|
||||
|
||||
-- |
|
||||
-- Decoder of the @JSONB@ values into a raw JSON 'ByteString'.
|
||||
-- Decoder of the @JSONB@ columns into a raw JSON 'ByteString'.
|
||||
--
|
||||
{-# INLINABLE jsonbBytes #-}
|
||||
jsonbBytes :: (ByteString -> Either Text a) -> Value a
|
||||
@ -456,7 +456,7 @@ jsonbBytes fn =
|
||||
Value (Value.decoder (const (A.jsonb_bytes fn)))
|
||||
|
||||
-- |
|
||||
-- Lifts a custom value decoder function to a 'Value' decoder.
|
||||
-- Lifts a custom column decoder function to a 'Value' decoder.
|
||||
--
|
||||
{-# INLINABLE custom #-}
|
||||
custom :: (Bool -> ByteString -> Either Text a) -> Value a
|
||||
@ -464,7 +464,7 @@ custom fn =
|
||||
Value (Value.decoderFn fn)
|
||||
|
||||
|
||||
-- ** Composite value decoders
|
||||
-- ** Composite column decoders
|
||||
-------------------------
|
||||
|
||||
-- |
|
||||
@ -484,9 +484,9 @@ composite (Composite imp) =
|
||||
Value (Value.decoder (Composite.run imp))
|
||||
|
||||
-- |
|
||||
-- A generic decoder of @HSTORE@ values.
|
||||
-- A generic decoder of @HSTORE@ columns.
|
||||
--
|
||||
-- Here's how you can use it to construct a specific value:
|
||||
-- Here's how you can use it to construct a specific column:
|
||||
--
|
||||
-- @
|
||||
-- x :: Value [(Text, Maybe Text)]
|
||||
@ -500,8 +500,8 @@ hstore replicateM =
|
||||
Value (Value.decoder (const (A.hstore replicateM A.text_strict A.text_strict)))
|
||||
|
||||
-- |
|
||||
-- Given a partial mapping from text to value,
|
||||
-- produces a decoder of that value.
|
||||
-- Given a partial mapping from text to column,
|
||||
-- produces a decoder of that column.
|
||||
enum :: (Text -> Maybe a) -> Value a
|
||||
enum mapping =
|
||||
Value (Value.decoder (const (A.enum mapping)))
|
||||
@ -643,12 +643,12 @@ instance Default (Value B.Value) where
|
||||
-- |
|
||||
-- A generic array decoder.
|
||||
--
|
||||
-- Here's how you can use it to produce a specific array value decoder:
|
||||
-- Here's how you can use it to produce a specific array column decoder:
|
||||
--
|
||||
-- @
|
||||
-- x :: Value [[Text]]
|
||||
-- x =
|
||||
-- array (arrayDimension 'replicateM' (arrayDimension 'replicateM' (arrayValue text)))
|
||||
-- array (dimension 'replicateM' (dimension 'replicateM' (element text)))
|
||||
-- @
|
||||
--
|
||||
newtype Array a =
|
||||
@ -663,28 +663,28 @@ newtype Array a =
|
||||
--
|
||||
-- * An implementation of the @replicateM@ function
|
||||
-- (@Control.Monad.'Control.Monad.replicateM'@, @Data.Vector.'Data.Vector.replicateM'@),
|
||||
-- which determines the output value.
|
||||
-- which determines the output column.
|
||||
--
|
||||
-- * A decoder of its components, which can be either another 'arrayDimension',
|
||||
-- 'arrayValue' or 'arrayNullableValue'.
|
||||
-- * A decoder of its components, which can be either another 'dimension',
|
||||
-- 'element' or 'nullableElement'.
|
||||
--
|
||||
{-# INLINABLE arrayDimension #-}
|
||||
arrayDimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
|
||||
arrayDimension replicateM (Array imp) =
|
||||
{-# 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)
|
||||
|
||||
-- |
|
||||
-- Lift a 'Value' decoder into an 'Array' decoder for parsing of non-nullable leaf values.
|
||||
{-# INLINABLE arrayValue #-}
|
||||
arrayValue :: Value a -> Array a
|
||||
arrayValue (Value imp) =
|
||||
-- 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) =
|
||||
Array (Array.nonNullValue (Value.run imp))
|
||||
|
||||
-- |
|
||||
-- Lift a 'Value' decoder into an 'Array' decoder for parsing of nullable leaf values.
|
||||
{-# INLINABLE arrayNullableValue #-}
|
||||
arrayNullableValue :: Value a -> Array (Maybe a)
|
||||
arrayNullableValue (Value imp) =
|
||||
-- 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) =
|
||||
Array (Array.value (Value.run imp))
|
||||
|
||||
|
||||
@ -692,22 +692,22 @@ arrayNullableValue (Value imp) =
|
||||
-------------------------
|
||||
|
||||
-- |
|
||||
-- Composable decoder of composite values (rows, records).
|
||||
-- Composable decoder of composite columns (rows, records).
|
||||
newtype Composite a =
|
||||
Composite (Composite.Composite a)
|
||||
deriving (Functor, Applicative, Monad)
|
||||
|
||||
-- |
|
||||
-- Lift a 'Value' decoder into a 'Composite' decoder for parsing of non-nullable leaf values.
|
||||
{-# INLINABLE compositeValue #-}
|
||||
compositeValue :: Value a -> Composite a
|
||||
compositeValue (Value imp) =
|
||||
-- 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) =
|
||||
Composite (Composite.nonNullValue (Value.run imp))
|
||||
|
||||
-- |
|
||||
-- Lift a 'Value' decoder into a 'Composite' decoder for parsing of nullable leaf values.
|
||||
{-# INLINABLE compositeNullableValue #-}
|
||||
compositeNullableValue :: Value a -> Composite (Maybe a)
|
||||
compositeNullableValue (Value imp) =
|
||||
-- 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) =
|
||||
Composite (Composite.value (Value.run imp))
|
||||
|
||||
|
@ -5,8 +5,8 @@ module Hasql.Encoders
|
||||
-- * Params
|
||||
Params,
|
||||
unit,
|
||||
value,
|
||||
nullableValue,
|
||||
param,
|
||||
nullableParam,
|
||||
-- * Value
|
||||
Value,
|
||||
bool,
|
||||
@ -36,9 +36,9 @@ module Hasql.Encoders
|
||||
unknown,
|
||||
-- * Array
|
||||
Array,
|
||||
arrayValue,
|
||||
arrayNullableValue,
|
||||
arrayDimension,
|
||||
element,
|
||||
nullableElement,
|
||||
dimension,
|
||||
-- ** Insert Many
|
||||
-- $insertMany
|
||||
)
|
||||
@ -68,7 +68,7 @@ import qualified Hasql.Private.Prelude as Prelude
|
||||
-- someParamsEncoder :: 'Params' (Int64, Maybe Text)
|
||||
-- someParamsEncoder =
|
||||
-- 'contramap' 'fst' ('value' 'int8') '<>'
|
||||
-- 'contramap' 'snd' ('nullableValue' 'text')
|
||||
-- 'contramap' 'snd' ('nullableParam' 'text')
|
||||
-- @
|
||||
--
|
||||
-- As a general solution for tuples of any arity, instead of 'fst' and 'snd',
|
||||
@ -79,7 +79,7 @@ import qualified Hasql.Private.Prelude as Prelude
|
||||
-- @
|
||||
-- someParamsEncoder :: 'Params' (Int64, Maybe Text)
|
||||
-- someParamsEncoder =
|
||||
-- 'contrazip2' ('value' 'int8') ('nullableValue' 'text')
|
||||
-- 'contrazip2' ('value' 'int8') ('nullableParam' 'text')
|
||||
-- @
|
||||
--
|
||||
-- Here's how you can implement encoders for custom composite types:
|
||||
@ -122,17 +122,17 @@ unit =
|
||||
-- |
|
||||
-- Lift an individual value encoder to a parameters encoder.
|
||||
--
|
||||
{-# INLINABLE value #-}
|
||||
value :: Value a -> Params a
|
||||
value (Value x) =
|
||||
{-# INLINABLE param #-}
|
||||
param :: Value a -> Params a
|
||||
param (Value x) =
|
||||
Params (Params.value x)
|
||||
|
||||
-- |
|
||||
-- Lift an individual nullable value encoder to a parameters encoder.
|
||||
--
|
||||
{-# INLINABLE nullableValue #-}
|
||||
nullableValue :: Value a -> Params (Maybe a)
|
||||
nullableValue (Value x) =
|
||||
{-# INLINABLE nullableParam #-}
|
||||
nullableParam :: Value a -> Params (Maybe a)
|
||||
nullableParam (Value x) =
|
||||
Params (Params.nullableValue x)
|
||||
|
||||
|
||||
@ -149,27 +149,27 @@ instance Default (Params ()) where
|
||||
instance Default (Value a) => Default (Params (Identity a)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
contramap runIdentity (value def)
|
||||
contramap runIdentity (param def)
|
||||
|
||||
instance (Default (Value a1), Default (Value a2)) => Default (Params (a1, a2)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
contrazip2 (value def) (value def)
|
||||
contrazip2 (param def) (param def)
|
||||
|
||||
instance (Default (Value a1), Default (Value a2), Default (Value a3)) => Default (Params (a1, a2, a3)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
contrazip3 (value def) (value def) (value def)
|
||||
contrazip3 (param def) (param def) (param def)
|
||||
|
||||
instance (Default (Value a1), Default (Value a2), Default (Value a3), Default (Value a4)) => Default (Params (a1, a2, a3, a4)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
contrazip4 (value def) (value def) (value def) (value def)
|
||||
contrazip4 (param def) (param def) (param def) (param def)
|
||||
|
||||
instance (Default (Value a1), Default (Value a2), Default (Value a3), Default (Value a4), Default (Value a5)) => Default (Params (a1, a2, a3, a4, a5)) where
|
||||
{-# INLINE def #-}
|
||||
def =
|
||||
contrazip5 (value def) (value def) (value def) (value def) (value def)
|
||||
contrazip5 (param def) (param def) (param def) (param def) (param def)
|
||||
|
||||
|
||||
-- * Value Encoder
|
||||
@ -494,7 +494,7 @@ instance Default (Value B.Value) where
|
||||
--
|
||||
-- >x :: Value [[Int64]]
|
||||
-- >x =
|
||||
-- > array (arrayDimension foldl' (arrayDimension foldl' (arrayValue int8)))
|
||||
-- > array (dimension foldl' (dimension foldl' (element int8)))
|
||||
--
|
||||
-- Please note that the PostgreSQL __IN__ keyword does not "accept" an array, but rather a syntactical list of
|
||||
-- values, thus this encoder is not suited for that. Use a **field** = ANY($1) query instead.
|
||||
@ -504,16 +504,16 @@ newtype Array a =
|
||||
|
||||
-- |
|
||||
-- Lifts the 'Value' encoder into the 'Array' encoder of a non-nullable value.
|
||||
{-# INLINABLE arrayValue #-}
|
||||
arrayValue :: Value a -> Array a
|
||||
arrayValue (Value (Value.Value elementOID arrayOID encoder renderer)) =
|
||||
{-# INLINABLE element #-}
|
||||
element :: Value a -> Array a
|
||||
element (Value (Value.Value elementOID arrayOID encoder renderer)) =
|
||||
Array (Array.value elementOID arrayOID encoder renderer)
|
||||
|
||||
-- |
|
||||
-- Lifts the 'Value' encoder into the 'Array' encoder of a nullable value.
|
||||
{-# INLINABLE arrayNullableValue #-}
|
||||
arrayNullableValue :: Value a -> Array (Maybe a)
|
||||
arrayNullableValue (Value (Value.Value elementOID arrayOID encoder renderer)) =
|
||||
{-# INLINABLE nullableElement #-}
|
||||
nullableElement :: Value a -> Array (Maybe a)
|
||||
nullableElement (Value (Value.Value elementOID arrayOID encoder renderer)) =
|
||||
Array (Array.nullableValue elementOID arrayOID encoder renderer)
|
||||
|
||||
-- |
|
||||
@ -526,12 +526,12 @@ arrayNullableValue (Value (Value.Value elementOID arrayOID encoder renderer)) =
|
||||
-- such as @Data.Foldable.'foldl''@,
|
||||
-- which determines the input value.
|
||||
--
|
||||
-- * A component encoder, which can be either another 'arrayDimension',
|
||||
-- 'arrayValue' or 'arrayNullableValue'.
|
||||
-- * A component encoder, which can be either another 'dimension',
|
||||
-- 'element' or 'nullableElement'.
|
||||
--
|
||||
{-# INLINABLE arrayDimension #-}
|
||||
arrayDimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c
|
||||
arrayDimension foldl (Array imp) =
|
||||
{-# INLINABLE dimension #-}
|
||||
dimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c
|
||||
dimension foldl (Array imp) =
|
||||
Array (Array.dimension foldl imp)
|
||||
|
||||
-- $insertMany
|
||||
@ -553,7 +553,7 @@ arrayDimension foldl (Array imp) =
|
||||
-- contrazip3 (vector Encoders.uuid) (vector Encoders.float8) (vector Encoders.float8)
|
||||
-- where
|
||||
-- vector value =
|
||||
-- Encoders.value (Encoders.array (Encoders.arrayDimension foldl' (Encoders.arrayValue value)))
|
||||
-- Encoders.value (Encoders.array (Encoders.dimension foldl' (Encoders.element value)))
|
||||
-- decoder =
|
||||
-- Decoders.unit
|
||||
-- @
|
@ -70,7 +70,7 @@ queryWithSingleRow =
|
||||
D.singleRow row
|
||||
where
|
||||
row =
|
||||
tuple <$> D.value D.int8 <*> D.value D.int8
|
||||
tuple <$> D.column D.int8 <*> D.column D.int8
|
||||
where
|
||||
tuple !a !b =
|
||||
(a, b)
|
||||
@ -84,7 +84,7 @@ queryWithManyRows decoder =
|
||||
encoder =
|
||||
conquer
|
||||
rowDecoder =
|
||||
tuple <$> D.value D.int8 <*> D.value D.int8
|
||||
tuple <$> D.column D.int8 <*> D.column D.int8
|
||||
where
|
||||
tuple !a !b =
|
||||
(a, b)
|
||||
|
@ -29,10 +29,10 @@ tree =
|
||||
where
|
||||
encoder =
|
||||
contrazip2
|
||||
(Encoders.value (Encoders.array (Encoders.arrayDimension foldl' (Encoders.arrayValue Encoders.int8))))
|
||||
(Encoders.value Encoders.text)
|
||||
(Encoders.param (Encoders.array (Encoders.dimension foldl' (Encoders.element Encoders.int8))))
|
||||
(Encoders.param Encoders.text)
|
||||
decoder =
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.value Decoders.bool))
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.column Decoders.bool))
|
||||
session =
|
||||
Session.query ([3, 7], "a") query
|
||||
in do
|
||||
@ -47,9 +47,9 @@ tree =
|
||||
Query.Query "select true where 1 = any ($1)" encoder decoder True
|
||||
where
|
||||
encoder =
|
||||
Encoders.value (Encoders.array (Encoders.arrayDimension foldl' (Encoders.arrayValue Encoders.int8)))
|
||||
Encoders.param (Encoders.array (Encoders.dimension foldl' (Encoders.element Encoders.int8)))
|
||||
decoder =
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.value Decoders.bool))
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.column Decoders.bool))
|
||||
session =
|
||||
do
|
||||
result1 <- Session.query [1, 2] query
|
||||
@ -65,9 +65,9 @@ tree =
|
||||
Query.Query "select true where 3 <> all ($1)" encoder decoder True
|
||||
where
|
||||
encoder =
|
||||
Encoders.value (Encoders.array (Encoders.arrayDimension foldl' (Encoders.arrayValue Encoders.int8)))
|
||||
Encoders.param (Encoders.array (Encoders.dimension foldl' (Encoders.element Encoders.int8)))
|
||||
decoder =
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.value Decoders.bool))
|
||||
fmap (maybe False (const True)) (Decoders.maybeRow (Decoders.column Decoders.bool))
|
||||
session =
|
||||
do
|
||||
result1 <- Session.query [1, 2] query
|
||||
@ -87,7 +87,7 @@ tree =
|
||||
encoder =
|
||||
Encoders.unit
|
||||
decoder =
|
||||
Decoders.singleRow (Decoders.value (Decoders.composite ((,) <$> Decoders.compositeValue Decoders.int8 <*> Decoders.compositeValue Decoders.bool)))
|
||||
Decoders.singleRow (Decoders.column (Decoders.composite ((,) <$> Decoders.field Decoders.int8 <*> Decoders.field Decoders.bool)))
|
||||
session =
|
||||
Session.query () query
|
||||
in do
|
||||
@ -105,14 +105,14 @@ tree =
|
||||
Encoders.unit
|
||||
decoder =
|
||||
Decoders.singleRow $
|
||||
(,) <$> Decoders.value entity1 <*> Decoders.value entity2
|
||||
(,) <$> Decoders.column entity1 <*> Decoders.column entity2
|
||||
where
|
||||
entity1 =
|
||||
Decoders.composite $
|
||||
(,) <$> Decoders.compositeValue Decoders.int8 <*> Decoders.compositeValue Decoders.bool
|
||||
(,) <$> Decoders.field Decoders.int8 <*> Decoders.field Decoders.bool
|
||||
entity2 =
|
||||
Decoders.composite $
|
||||
(,) <$> Decoders.compositeValue Decoders.text <*> Decoders.compositeValue Decoders.int8
|
||||
(,) <$> Decoders.field Decoders.text <*> Decoders.field Decoders.int8
|
||||
session =
|
||||
Session.query () query
|
||||
in do
|
||||
@ -137,7 +137,7 @@ tree =
|
||||
encoder =
|
||||
Encoders.unit
|
||||
decoder =
|
||||
Decoders.singleRow (Decoders.value (Decoders.array (Decoders.arrayDimension replicateM (Decoders.arrayValue Decoders.int8))))
|
||||
Decoders.singleRow (Decoders.column (Decoders.array (Decoders.dimension replicateM (Decoders.element Decoders.int8))))
|
||||
in io
|
||||
,
|
||||
testCase "Failing prepared statements" $
|
||||
@ -185,9 +185,9 @@ tree =
|
||||
sql =
|
||||
"select $1 :: int8"
|
||||
encoder =
|
||||
Encoders.value Encoders.int8
|
||||
Encoders.param Encoders.int8
|
||||
decoder =
|
||||
Decoders.singleRow $ Decoders.value Decoders.int8
|
||||
Decoders.singleRow $ Decoders.column Decoders.int8
|
||||
fail =
|
||||
catchError (Session.sql "absurd") (const (pure ()))
|
||||
in io
|
||||
@ -201,10 +201,10 @@ tree =
|
||||
sql =
|
||||
"select ($1 + $2)"
|
||||
encoder =
|
||||
contramap fst (Encoders.value Encoders.int8) <>
|
||||
contramap snd (Encoders.value Encoders.int8)
|
||||
contramap fst (Encoders.param Encoders.int8) <>
|
||||
contramap snd (Encoders.param Encoders.int8)
|
||||
decoder =
|
||||
Decoders.singleRow (Decoders.value Decoders.int8)
|
||||
Decoders.singleRow (Decoders.column Decoders.int8)
|
||||
sumSession :: Session.Session Int64
|
||||
sumSession =
|
||||
Session.sql "begin" *> Session.query (1, 1) sumQuery <* Session.sql "end"
|
||||
@ -226,10 +226,10 @@ tree =
|
||||
sql =
|
||||
"select ($1 + $2)"
|
||||
encoder =
|
||||
contramap fst (Encoders.value Encoders.int8) <>
|
||||
contramap snd (Encoders.value Encoders.int8)
|
||||
contramap fst (Encoders.param Encoders.int8) <>
|
||||
contramap snd (Encoders.param Encoders.int8)
|
||||
decoder =
|
||||
Decoders.singleRow (Decoders.value Decoders.int8)
|
||||
Decoders.singleRow (Decoders.column Decoders.int8)
|
||||
session :: Session.Session Int64
|
||||
session =
|
||||
do
|
||||
@ -253,9 +253,9 @@ tree =
|
||||
sql =
|
||||
"select $1 = interval '10 seconds'"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.bool)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.bool)))
|
||||
encoder =
|
||||
Encoders.value (Encoders.interval)
|
||||
Encoders.param (Encoders.interval)
|
||||
in DSL.query (10 :: DiffTime) query
|
||||
in actualIO >>= \x -> assertEqual (show x) (Right True) x
|
||||
,
|
||||
@ -270,7 +270,7 @@ tree =
|
||||
sql =
|
||||
"select interval '10 seconds'"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.interval)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.interval)))
|
||||
encoder =
|
||||
Encoders.unit
|
||||
in DSL.query () query
|
||||
@ -287,9 +287,9 @@ tree =
|
||||
sql =
|
||||
"select $1"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.interval)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.interval)))
|
||||
encoder =
|
||||
Encoders.value (Encoders.interval)
|
||||
Encoders.param (Encoders.interval)
|
||||
in DSL.query (10 :: DiffTime) query
|
||||
in actualIO >>= \x -> assertEqual (show x) (Right (10 :: DiffTime)) x
|
||||
,
|
||||
@ -318,9 +318,9 @@ tree =
|
||||
sql =
|
||||
"select $1 = ('ok' :: mood)"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.bool)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.bool)))
|
||||
encoder =
|
||||
Encoders.value (Encoders.unknown)
|
||||
Encoders.param (Encoders.unknown)
|
||||
in DSL.query "ok" query
|
||||
in actualIO >>= assertEqual "" (Right True)
|
||||
,
|
||||
@ -349,9 +349,9 @@ tree =
|
||||
sql =
|
||||
"select overloaded($1, $2) || overloaded($3, $4, $5)"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.text)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.text)))
|
||||
encoder =
|
||||
contramany (Encoders.value Encoders.unknown)
|
||||
contramany (Encoders.param Encoders.unknown)
|
||||
in DSL.query ["1", "2", "4", "5", "6"] query
|
||||
in actualIO >>= assertEqual "" (Right "3456")
|
||||
,
|
||||
@ -380,9 +380,9 @@ tree =
|
||||
sql =
|
||||
"select ($1 :: mood)"
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.enum (Just . id))))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.enum (Just . id))))
|
||||
encoder =
|
||||
Encoders.value (Encoders.enum id)
|
||||
Encoders.param (Encoders.enum id)
|
||||
in DSL.query "ok" query
|
||||
in actualIO >>= assertEqual "" (Right "ok")
|
||||
,
|
||||
@ -400,9 +400,9 @@ tree =
|
||||
sql =
|
||||
"select $1"
|
||||
encoder =
|
||||
Encoders.value Encoders.text
|
||||
Encoders.param Encoders.text
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value (Decoders.text)))
|
||||
(Decoders.singleRow (Decoders.column (Decoders.text)))
|
||||
effect2 =
|
||||
DSL.query 1 query
|
||||
where
|
||||
@ -412,9 +412,9 @@ tree =
|
||||
sql =
|
||||
"select $1"
|
||||
encoder =
|
||||
Encoders.value Encoders.int8
|
||||
Encoders.param Encoders.int8
|
||||
decoder =
|
||||
(Decoders.singleRow (Decoders.value Decoders.int8))
|
||||
(Decoders.singleRow (Decoders.column Decoders.int8))
|
||||
in (,) <$> effect1 <*> effect2
|
||||
in actualIO >>= assertEqual "" (Right ("ok", 1))
|
||||
,
|
||||
@ -452,8 +452,8 @@ tree =
|
||||
DSL.session $ do
|
||||
DSL.query () $ Queries.plain $ "drop table if exists a"
|
||||
DSL.query () $ Queries.plain $ "create table a (id serial not null, v char not null, primary key (id))"
|
||||
id1 <- DSL.query () $ Query.Query "insert into a (v) values ('a') returning id" def (Decoders.singleRow (Decoders.value Decoders.int4)) False
|
||||
id2 <- DSL.query () $ Query.Query "insert into a (v) values ('b') returning id" def (Decoders.singleRow (Decoders.value Decoders.int4)) False
|
||||
id1 <- DSL.query () $ Query.Query "insert into a (v) values ('a') returning id" def (Decoders.singleRow (Decoders.column Decoders.int4)) False
|
||||
id2 <- DSL.query () $ Query.Query "insert into a (v) values ('b') returning id" def (Decoders.singleRow (Decoders.column Decoders.int4)) False
|
||||
DSL.query () $ Queries.plain $ "drop table if exists a"
|
||||
pure (id1, id2)
|
||||
in assertEqual "" (Right (1, 2)) =<< actualIO
|
||||
|
@ -33,4 +33,4 @@ selectList =
|
||||
sql =
|
||||
"values (1,2), (3,4), (5,6)"
|
||||
decoder =
|
||||
HD.rowsList ((,) <$> HD.value HD.int8 <*> HD.value HD.int8)
|
||||
HD.rowsList ((,) <$> HD.column HD.int8 <*> HD.column HD.int8)
|
||||
|
@ -13,7 +13,7 @@ selectSleep =
|
||||
sql =
|
||||
"select pg_sleep($1)"
|
||||
encoder =
|
||||
E.value E.float8
|
||||
E.param E.float8
|
||||
decoder =
|
||||
D.unit
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user