{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language MonoLocalBinds #-}
{-# language MultiWayIf #-}
{-# language StandaloneKindSignatures #-}
{-# language UndecidableInstances #-}
module Rel8.Type
( DBType (typeInformation)
)
where
import Data.Aeson ( Value )
import qualified Data.Aeson as Aeson
import Data.Int ( Int16, Int32, Int64 )
import Data.List.NonEmpty ( NonEmpty )
import Data.Kind ( Constraint, Type )
import Prelude
import Data.ByteString ( ByteString )
import qualified Data.ByteString.Lazy as Lazy ( ByteString )
import qualified Data.ByteString.Lazy as ByteString ( fromStrict, toStrict )
import Data.CaseInsensitive ( CI )
import qualified Data.CaseInsensitive as CI
import qualified Hasql.Decoders as Hasql
import qualified Opaleye.Internal.HaskellDB.PrimQuery as Opaleye
import qualified Opaleye.Internal.HaskellDB.Sql.Default as Opaleye ( quote )
import Rel8.Schema.Null ( NotNull, Sql, nullable )
import Rel8.Type.Array ( listTypeInformation, nonEmptyTypeInformation )
import Rel8.Type.Information ( TypeInformation(..), mapTypeInformation )
import Data.Scientific ( Scientific )
import Data.Text ( Text )
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Lazy ( Text, unpack )
import qualified Data.Text.Lazy as Text ( fromStrict, toStrict )
import qualified Data.Text.Lazy.Encoding as Lazy ( decodeUtf8 )
import Data.Time.Calendar ( Day )
import Data.Time.Clock ( UTCTime )
import Data.Time.LocalTime
( CalendarDiffTime( CalendarDiffTime )
, LocalTime
, TimeOfDay
)
import Data.Time.Format ( formatTime, defaultTimeLocale )
import Data.UUID ( UUID )
import qualified Data.UUID as UUID
type DBType :: Type -> Constraint
class NotNull a => DBType a where
typeInformation :: TypeInformation a
instance DBType Bool where
typeInformation :: TypeInformation Bool
typeInformation = TypeInformation
{ encode :: Bool -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Literal
Opaleye.BoolLit
, decode :: Value Bool
decode = Value Bool
Hasql.bool
, typeName :: String
typeName = String
"bool"
}
instance DBType Char where
typeInformation :: TypeInformation Char
typeInformation = TypeInformation
{ encode :: Char -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
, decode :: Value Char
decode = Value Char
Hasql.char
, typeName :: String
typeName = String
"char"
}
instance DBType Int16 where
typeInformation :: TypeInformation Int16
typeInformation = TypeInformation
{ encode :: Int16 -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
Opaleye.IntegerLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
, decode :: Value Int16
decode = Value Int16
Hasql.int2
, typeName :: String
typeName = String
"int2"
}
instance DBType Int32 where
typeInformation :: TypeInformation Int32
typeInformation = TypeInformation
{ encode :: Int32 -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
Opaleye.IntegerLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
, decode :: Value Int32
decode = Value Int32
Hasql.int4
, typeName :: String
typeName = String
"int4"
}
instance DBType Int64 where
typeInformation :: TypeInformation Int64
typeInformation = TypeInformation
{ encode :: Int64 -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
Opaleye.IntegerLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
, decode :: Value Int64
decode = Value Int64
Hasql.int8
, typeName :: String
typeName = String
"int8"
}
instance DBType Float where
typeInformation :: TypeInformation Float
typeInformation = TypeInformation
{ encode :: Float -> PrimExpr
encode = \Float
x -> Literal -> PrimExpr
Opaleye.ConstExpr
if | Float
x forall a. Eq a => a -> a -> Bool
== (Float
1 forall a. Fractional a => a -> a -> a
/ Float
0) -> String -> Literal
Opaleye.OtherLit String
"'Infinity'"
| forall a. RealFloat a => a -> Bool
isNaN Float
x -> String -> Literal
Opaleye.OtherLit String
"'NaN'"
| Float
x forall a. Eq a => a -> a -> Bool
== (-Float
1 forall a. Fractional a => a -> a -> a
/ Float
0) -> String -> Literal
Opaleye.OtherLit String
"'-Infinity'"
| Bool
otherwise -> Scientific -> Literal
Opaleye.NumericLit forall a b. (a -> b) -> a -> b
$ forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x
, decode :: Value Float
decode = Value Float
Hasql.float4
, typeName :: String
typeName = String
"float4"
}
instance DBType Double where
typeInformation :: TypeInformation Double
typeInformation = TypeInformation
{ encode :: Double -> PrimExpr
encode = \Double
x -> Literal -> PrimExpr
Opaleye.ConstExpr
if | Double
x forall a. Eq a => a -> a -> Bool
== (Double
1 forall a. Fractional a => a -> a -> a
/ Double
0) -> String -> Literal
Opaleye.OtherLit String
"'Infinity'"
| forall a. RealFloat a => a -> Bool
isNaN Double
x -> String -> Literal
Opaleye.OtherLit String
"'NaN'"
| Double
x forall a. Eq a => a -> a -> Bool
== (-Double
1 forall a. Fractional a => a -> a -> a
/ Double
0) -> String -> Literal
Opaleye.OtherLit String
"'-Infinity'"
| Bool
otherwise -> Scientific -> Literal
Opaleye.NumericLit forall a b. (a -> b) -> a -> b
$ forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
, decode :: Value Double
decode = Value Double
Hasql.float8
, typeName :: String
typeName = String
"float8"
}
instance DBType Scientific where
typeInformation :: TypeInformation Scientific
typeInformation = TypeInformation
{ encode :: Scientific -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Literal
Opaleye.NumericLit
, decode :: Value Scientific
decode = Value Scientific
Hasql.numeric
, typeName :: String
typeName = String
"numeric"
}
instance DBType UTCTime where
typeInformation :: TypeInformation UTCTime
typeInformation = TypeInformation
{ encode :: UTCTime -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"'%FT%T%QZ'"
, decode :: Value UTCTime
decode = Value UTCTime
Hasql.timestamptz
, typeName :: String
typeName = String
"timestamptz"
}
instance DBType Day where
typeInformation :: TypeInformation Day
typeInformation = TypeInformation
{ encode :: Day -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"'%F'"
, decode :: Value Day
decode = Value Day
Hasql.date
, typeName :: String
typeName = String
"date"
}
instance DBType LocalTime where
typeInformation :: TypeInformation LocalTime
typeInformation = TypeInformation
{ encode :: LocalTime -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"'%FT%T%Q'"
, decode :: Value LocalTime
decode = Value LocalTime
Hasql.timestamp
, typeName :: String
typeName = String
"timestamp"
}
instance DBType TimeOfDay where
typeInformation :: TypeInformation TimeOfDay
typeInformation = TypeInformation
{ encode :: TimeOfDay -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"'%T%Q'"
, decode :: Value TimeOfDay
decode = Value TimeOfDay
Hasql.time
, typeName :: String
typeName = String
"time"
}
instance DBType CalendarDiffTime where
typeInformation :: TypeInformation CalendarDiffTime
typeInformation = TypeInformation
{ encode :: CalendarDiffTime -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"'%bmon %0Es'"
, decode :: Value CalendarDiffTime
decode = Integer -> NominalDiffTime -> CalendarDiffTime
CalendarDiffTime Integer
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value DiffTime
Hasql.interval
, typeName :: String
typeName = String
"interval"
}
instance DBType Text where
typeInformation :: TypeInformation Text
typeInformation = TypeInformation
{ encode :: Text -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
, decode :: Value Text
decode = Value Text
Hasql.text
, typeName :: String
typeName = String
"text"
}
instance DBType Lazy.Text where
typeInformation :: TypeInformation Text
typeInformation =
forall a b.
(a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b
mapTypeInformation Text -> Text
Text.fromStrict Text -> Text
Text.toStrict forall a. DBType a => TypeInformation a
typeInformation
instance DBType (CI Text) where
typeInformation :: TypeInformation (CI Text)
typeInformation = forall a b.
(a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b
mapTypeInformation forall s. FoldCase s => s -> CI s
CI.mk forall s. CI s -> s
CI.original forall a. DBType a => TypeInformation a
typeInformation
{ typeName :: String
typeName = String
"citext"
}
instance DBType (CI Lazy.Text) where
typeInformation :: TypeInformation (CI Text)
typeInformation = forall a b.
(a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b
mapTypeInformation forall s. FoldCase s => s -> CI s
CI.mk forall s. CI s -> s
CI.original forall a. DBType a => TypeInformation a
typeInformation
{ typeName :: String
typeName = String
"citext"
}
instance DBType ByteString where
typeInformation :: TypeInformation ByteString
typeInformation = TypeInformation
{ encode :: ByteString -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Literal
Opaleye.ByteStringLit
, decode :: Value ByteString
decode = Value ByteString
Hasql.bytea
, typeName :: String
typeName = String
"bytea"
}
instance DBType Lazy.ByteString where
typeInformation :: TypeInformation ByteString
typeInformation =
forall a b.
(a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b
mapTypeInformation ByteString -> ByteString
ByteString.fromStrict ByteString -> ByteString
ByteString.toStrict
forall a. DBType a => TypeInformation a
typeInformation
instance DBType UUID where
typeInformation :: TypeInformation UUID
typeInformation = TypeInformation
{ encode :: UUID -> PrimExpr
encode = Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
UUID.toString
, decode :: Value UUID
decode = Value UUID
Hasql.uuid
, typeName :: String
typeName = String
"uuid"
}
instance DBType Value where
typeInformation :: TypeInformation Value
typeInformation = TypeInformation
{ encode :: Value -> PrimExpr
encode =
Literal -> PrimExpr
Opaleye.ConstExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
Opaleye.OtherLit forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> String
Opaleye.quote forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> String
Lazy.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Lazy.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Aeson.encode
, decode :: Value Value
decode = Value Value
Hasql.jsonb
, typeName :: String
typeName = String
"jsonb"
}
instance Sql DBType a => DBType [a] where
typeInformation :: TypeInformation [a]
typeInformation = forall a.
Nullity a -> TypeInformation (Unnullify a) -> TypeInformation [a]
listTypeInformation forall a. Nullable a => Nullity a
nullable forall a. DBType a => TypeInformation a
typeInformation
instance Sql DBType a => DBType (NonEmpty a) where
typeInformation :: TypeInformation (NonEmpty a)
typeInformation = forall a.
Nullity a
-> TypeInformation (Unnullify a) -> TypeInformation (NonEmpty a)
nonEmptyTypeInformation forall a. Nullable a => Nullity a
nullable forall a. DBType a => TypeInformation a
typeInformation