hasql/library/Hasql/Encoding.hs

484 lines
11 KiB
Haskell
Raw Normal View History

2015-11-21 16:42:12 +03:00
-- |
-- A DSL for declaration of query parameter encoders.
2015-11-21 13:36:01 +03:00
module Hasql.Encoding
2015-11-08 21:09:42 +03:00
(
-- * Params
Params,
2015-11-22 09:08:06 +03:00
unit,
2015-11-08 21:09:42 +03:00
value,
nullableValue,
-- * Value
Value,
bool,
int2,
int4,
int8,
float4,
float8,
numeric,
char,
text,
bytea,
date,
timestamp,
timestamptz,
time,
timetz,
interval,
uuid,
json,
array,
2015-11-10 17:53:14 +03:00
enum,
2015-11-08 21:09:42 +03:00
-- * Array
Array,
arrayValue,
arrayNullableValue,
arrayDimension,
)
where
import Hasql.Prelude hiding (bool)
import qualified PostgreSQL.Binary.Encoder as Encoder
import qualified Data.Aeson as Aeson
2015-11-21 13:36:01 +03:00
import qualified Hasql.Encoding.Params as Params
import qualified Hasql.Encoding.Value as Value
import qualified Hasql.Encoding.Array as Array
2015-11-08 21:09:42 +03:00
import qualified Hasql.PTI as PTI
import qualified Hasql.Prelude as Prelude
2015-11-21 13:36:01 +03:00
-- * Parameters Product Encoder
2015-11-08 21:09:42 +03:00
-------------------------
-- |
2015-11-21 13:36:01 +03:00
-- Encoder of some representation of the parameters product.
2015-11-08 21:09:42 +03:00
--
-- Has instances of 'Contravariant', 'Divisible' and 'Monoid',
-- which you can use to compose multiple parameters together.
-- E.g.,
--
2015-11-09 07:10:40 +03:00
-- @
2015-11-21 18:07:49 +03:00
-- someParamsEncoder :: 'Params' (Int64, Maybe Text)
2015-11-21 13:36:01 +03:00
-- someParamsEncoder =
2015-11-21 18:07:49 +03:00
-- 'contramap' 'fst' ('value' 'int8') '<>'
-- 'contramap' 'snd' ('nullableValue' 'text')
2015-11-09 07:10:40 +03:00
-- @
--
-- As a general solution for tuples of any arity, instead of 'fst' and 'snd',
2015-11-21 18:03:29 +03:00
-- consider the functions of the @contrazip@ family
-- from the \"contravariant-extras\" package.
-- E.g., here's how you can achieve the same as the above:
2015-11-09 07:10:40 +03:00
--
-- @
2015-11-21 18:07:49 +03:00
-- someParamsEncoder :: 'Params' (Int64, Maybe Text)
2015-11-21 13:36:01 +03:00
-- someParamsEncoder =
2015-11-21 18:07:49 +03:00
-- 'contrazip2' ('value' 'int8') ('nullableValue' 'text')
2015-11-09 07:10:40 +03:00
-- @
2015-11-08 21:09:42 +03:00
--
2015-11-21 16:22:38 +03:00
-- Here's how you can implement encoders for custom composite types:
--
-- @
-- data Person =
-- Person { name :: Text, gender :: Gender, age :: Int }
--
-- data Gender =
-- Male | Female
--
2015-11-21 18:07:49 +03:00
-- personParams :: 'Params' Person
2015-11-21 16:22:38 +03:00
-- personParams =
2015-11-21 18:07:49 +03:00
-- 'contramap' name ('value' 'text') '<>'
-- 'contramap' gender ('value' genderValue) '<>'
-- 'contramap' (fromIntegral . age) ('value' 'int8')
2015-11-21 16:22:38 +03:00
--
2015-11-21 18:07:49 +03:00
-- genderValue :: 'Value' Gender
2015-11-21 16:22:38 +03:00
-- genderValue =
2015-11-21 18:07:49 +03:00
-- 'contramap' genderText 'text'
2015-11-21 16:22:38 +03:00
-- where
-- genderText gender =
-- case gender of
-- Male -> "male"
-- Female -> "female"
-- @
--
2015-11-08 21:09:42 +03:00
newtype Params a =
Params (Params.Params a)
deriving (Contravariant, Divisible, Monoid)
2015-11-22 09:08:06 +03:00
-- |
-- Encode no parameters.
--
{-# INLINABLE unit #-}
unit :: Params ()
unit =
Params mempty
2015-11-08 21:09:42 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- Lift an individual value encoder to a parameters encoder.
2015-11-08 21:09:42 +03:00
--
{-# INLINABLE value #-}
value :: Value a -> Params a
value (Value x) =
Params (Params.value x)
-- |
2015-11-21 13:36:01 +03:00
-- Lift an individual nullable value encoder to a parameters encoder.
2015-11-08 21:09:42 +03:00
--
{-# INLINABLE nullableValue #-}
nullableValue :: Value a -> Params (Maybe a)
nullableValue (Value x) =
Params (Params.nullableValue x)
-- ** Instances
-------------------------
2015-11-22 09:08:06 +03:00
-- |
-- Maps to 'unit'.
2015-11-15 14:45:56 +03:00
instance Default (Params ()) where
{-# INLINE def #-}
def =
2015-11-22 09:08:06 +03:00
unit
2015-11-15 14:45:56 +03:00
2015-11-08 21:09:42 +03:00
instance Default (Value a) => Default (Params (Identity a)) where
{-# INLINE def #-}
def =
contramap runIdentity (value def)
instance (Default (Value a1), Default (Value a2)) => Default (Params (a1, a2)) where
{-# INLINE def #-}
def =
2015-11-22 09:07:58 +03:00
contrazip2 (value def) (value 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)
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)
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)
2015-11-08 21:09:42 +03:00
2015-11-21 13:36:01 +03:00
-- * Value Encoder
2015-11-08 21:09:42 +03:00
-------------------------
-- |
2015-11-21 13:36:01 +03:00
-- An individual value encoder.
2015-11-08 21:09:42 +03:00
-- Will be mapped to a single placeholder in the query.
--
newtype Value a =
Value (Value.Value a)
deriving (Contravariant)
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @BOOL@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE bool #-}
bool :: Value Bool
bool =
Value (Value.unsafePTI PTI.bool (const Encoder.bool))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @INT2@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE int2 #-}
int2 :: Value Int16
int2 =
Value (Value.unsafePTI PTI.int2 (const Encoder.int2_int16))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @INT4@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE int4 #-}
int4 :: Value Int32
int4 =
Value (Value.unsafePTI PTI.int4 (const Encoder.int4_int32))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @INT8@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE int8 #-}
int8 :: Value Int64
int8 =
Value (Value.unsafePTI PTI.int8 (const Encoder.int8_int64))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @FLOAT4@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE float4 #-}
float4 :: Value Float
float4 =
Value (Value.unsafePTI PTI.float4 (const Encoder.float4))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @FLOAT8@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE float8 #-}
float8 :: Value Double
float8 =
Value (Value.unsafePTI PTI.float8 (const Encoder.float8))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @NUMERIC@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE numeric #-}
numeric :: Value Scientific
numeric =
Value (Value.unsafePTI PTI.numeric (const Encoder.numeric))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @CHAR@ values.
-- Note that it supports UTF-8 values and
-- identifies itself under the @TEXT@ OID because of that.
2015-11-08 21:09:42 +03:00
{-# INLINABLE char #-}
char :: Value Char
char =
Value (Value.unsafePTI PTI.text (const Encoder.char))
2015-11-08 21:09:42 +03:00
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @TEXT@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE text #-}
text :: Value Text
text =
Value (Value.unsafePTI PTI.text (const Encoder.text_strict))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @BYTEA@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE bytea #-}
bytea :: Value ByteString
bytea =
Value (Value.unsafePTI PTI.bytea (const Encoder.bytea_strict))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @DATE@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE date #-}
date :: Value Day
date =
Value (Value.unsafePTI PTI.date (const Encoder.date))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @TIMESTAMP@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE timestamp #-}
timestamp :: Value LocalTime
timestamp =
Value (Value.unsafePTI PTI.timestamp (Prelude.bool Encoder.timestamp_int Encoder.timestamp_float))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @TIMESTAMPTZ@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE timestamptz #-}
timestamptz :: Value UTCTime
timestamptz =
Value (Value.unsafePTI PTI.timestamptz (Prelude.bool Encoder.timestamptz_int Encoder.timestamptz_float))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @TIME@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE time #-}
time :: Value TimeOfDay
time =
Value (Value.unsafePTI PTI.time (Prelude.bool Encoder.time_int Encoder.time_float))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @TIMETZ@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE timetz #-}
timetz :: Value (TimeOfDay, TimeZone)
timetz =
Value (Value.unsafePTI PTI.timetz (Prelude.bool Encoder.timetz_int Encoder.timetz_float))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @INTERVAL@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE interval #-}
interval :: Value DiffTime
interval =
Value (Value.unsafePTI PTI.interval (Prelude.bool Encoder.interval_int Encoder.interval_float))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @UUID@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE uuid #-}
uuid :: Value UUID
uuid =
Value (Value.unsafePTI PTI.uuid (const Encoder.uuid))
2015-11-21 16:46:16 +03:00
-- |
-- Encoder of @JSON@ values.
2015-11-08 21:09:42 +03:00
{-# INLINABLE json #-}
json :: Value Aeson.Value
json =
Value (Value.unsafePTI PTI.json (const Encoder.json))
2015-11-09 07:10:40 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- Unlifts the 'Array' encoder to the plain 'Value' encoder.
2015-11-08 21:09:42 +03:00
{-# INLINABLE array #-}
array :: Array a -> Value a
array (Array imp) =
Array.run imp & \(arrayOID, encoder') ->
Value (Value.Value arrayOID arrayOID encoder')
2015-11-10 17:53:14 +03:00
-- |
-- Given a function,
-- which maps the value into the textual enum label from the DB side,
2015-11-21 13:36:01 +03:00
-- produces a encoder of that value.
2015-11-10 17:53:14 +03:00
{-# INLINABLE enum #-}
enum :: (a -> Text) -> Value a
enum mapping =
Value (Value.unsafePTI PTI.text (const (Encoder.enum mapping)))
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'.
instance Default (Value Scientific) where
{-# 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'.
instance Default (Value Day) where
{-# INLINE def #-}
def =
date
-- | Maps to 'timestamp'.
instance Default (Value LocalTime) where
{-# INLINE def #-}
def =
timestamp
-- | Maps to 'timestamptz'.
instance Default (Value UTCTime) where
{-# INLINE def #-}
def =
timestamptz
-- | Maps to 'time'.
instance Default (Value TimeOfDay) where
{-# INLINE def #-}
def =
time
-- | Maps to 'timetz'.
instance Default (Value (TimeOfDay, TimeZone)) where
{-# INLINE def #-}
def =
timetz
-- | Maps to 'interval'.
instance Default (Value DiffTime) where
{-# INLINE def #-}
def =
interval
-- | Maps to 'uuid'.
instance Default (Value UUID) where
{-# INLINE def #-}
def =
uuid
-- | Maps to 'json'.
instance Default (Value Aeson.Value) where
{-# INLINE def #-}
def =
json
-- * Array
-------------------------
2015-11-09 07:10:40 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- A generic array encoder.
2015-11-09 07:10:40 +03:00
--
-- Here's an example of its usage:
--
-- >x :: Value [[Int64]]
-- >x =
-- > array (arrayDimension foldl' (arrayDimension foldl' (arrayValue int8)))
--
2015-11-08 21:09:42 +03:00
newtype Array a =
Array (Array.Array a)
2015-11-09 07:10:40 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- Lifts the 'Value' encoder into the 'Array' encoder of a non-nullable value.
2015-11-08 21:09:42 +03:00
{-# INLINABLE arrayValue #-}
arrayValue :: Value a -> Array a
arrayValue (Value (Value.Value elementOID arrayOID encoder')) =
Array (Array.value elementOID arrayOID encoder')
2015-11-09 07:10:40 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- Lifts the 'Value' encoder into the 'Array' encoder of a nullable value.
2015-11-08 21:09:42 +03:00
{-# INLINABLE arrayNullableValue #-}
arrayNullableValue :: Value a -> Array (Maybe a)
arrayNullableValue (Value (Value.Value elementOID arrayOID encoder')) =
Array (Array.nullableValue elementOID arrayOID encoder')
2015-11-09 07:10:40 +03:00
-- |
2015-11-21 13:36:01 +03:00
-- A encoder of an array dimension,
2015-11-09 07:10:40 +03:00
-- which thus provides support for multidimensional arrays.
--
-- Accepts:
--
-- * An implementation of the left-fold operation,
-- such as @Data.Foldable.'foldl''@,
-- which determines the input value.
--
2015-11-21 13:36:01 +03:00
-- * A component encoder, which can be either another 'arrayDimension',
2015-11-09 07:10:40 +03:00
-- 'arrayValue' or 'arrayNullableValue'.
--
2015-11-08 21:09:42 +03:00
{-# INLINABLE arrayDimension #-}
arrayDimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c
arrayDimension foldl (Array imp) =
Array (Array.dimension foldl imp)