module Opaleye.SQLite.Internal.PGTypes where

import           Opaleye.SQLite.Internal.Column (Column(Column))
import qualified Opaleye.SQLite.Internal.HaskellDB.PrimQuery as HPQ

import qualified Data.Text as SText
import qualified Data.Text.Encoding as STextEncoding
import qualified Data.Text.Lazy as LText
import qualified Data.Text.Lazy.Encoding as LTextEncoding
import qualified Data.ByteString as SByteString
import qualified Data.ByteString.Lazy as LByteString
import qualified Data.Time as Time
import qualified Data.Time.Locale.Compat as Locale

-- FIXME: SQLite requires temporal types to have the type "TEXT" which
-- may cause problems elsewhere.
unsafePgFormatTime :: Time.FormatTime t => HPQ.Name -> String -> t -> Column c
unsafePgFormatTime :: Name -> Name -> t -> Column c
unsafePgFormatTime Name
_typeName Name
formatString = Name -> Name -> Column c
forall c. Name -> Name -> Column c
castToType Name
"TEXT" (Name -> Column c) -> (t -> Name) -> t -> Column c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Name
format
  where format :: t -> Name
format = TimeLocale -> Name -> t -> Name
forall t. FormatTime t => TimeLocale -> Name -> t -> Name
Time.formatTime TimeLocale
Locale.defaultTimeLocale Name
formatString

literalColumn :: HPQ.Literal -> Column a
literalColumn :: Literal -> Column a
literalColumn = PrimExpr -> Column a
forall a. PrimExpr -> Column a
Column (PrimExpr -> Column a)
-> (Literal -> PrimExpr) -> Literal -> Column a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Literal -> PrimExpr
HPQ.ConstExpr

castToType :: HPQ.Name -> String -> Column c
castToType :: Name -> Name -> Column c
castToType Name
typeName =
    PrimExpr -> Column c
forall a. PrimExpr -> Column a
Column (PrimExpr -> Column c) -> (Name -> PrimExpr) -> Name -> Column c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> PrimExpr -> PrimExpr
HPQ.CastExpr Name
typeName (PrimExpr -> PrimExpr) -> (Name -> PrimExpr) -> Name -> PrimExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Literal -> PrimExpr
HPQ.ConstExpr (Literal -> PrimExpr) -> (Name -> Literal) -> Name -> PrimExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Literal
HPQ.OtherLit

strictDecodeUtf8 :: SByteString.ByteString -> String
strictDecodeUtf8 :: ByteString -> Name
strictDecodeUtf8 = Text -> Name
SText.unpack (Text -> Name) -> (ByteString -> Text) -> ByteString -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
STextEncoding.decodeUtf8

lazyDecodeUtf8 :: LByteString.ByteString -> String
lazyDecodeUtf8 :: ByteString -> Name
lazyDecodeUtf8 = Text -> Name
LText.unpack (Text -> Name) -> (ByteString -> Text) -> ByteString -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LTextEncoding.decodeUtf8