{-# LANGUAGE DerivingStrategies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Preql.Wire.Orphans where
import Data.Aeson (FromJSON(..), ToJSON(..), Value(..), withScientific)
import Data.Scientific (toBoundedInteger)
import qualified Database.PostgreSQL.LibPQ as PQ
instance ToJSON PQ.Oid where
toJSON :: Oid -> Value
toJSON (PQ.Oid CUInt
oid) = Scientific -> Value
Number (CUInt -> Scientific
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
oid)
instance FromJSON PQ.Oid where
parseJSON :: Value -> Parser Oid
parseJSON = String -> (Scientific -> Parser Oid) -> Value -> Parser Oid
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific String
"Oid" ((Scientific -> Parser Oid) -> Value -> Parser Oid)
-> (Scientific -> Parser Oid) -> Value -> Parser Oid
forall a b. (a -> b) -> a -> b
$ \Scientific
sci ->
case Scientific -> Maybe CUInt
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger Scientific
sci of
Just CUInt
i -> Oid -> Parser Oid
forall (m :: * -> *) a. Monad m => a -> m a
return (CUInt -> Oid
PQ.Oid CUInt
i)
Maybe CUInt
Nothing -> String -> Parser Oid
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expected integer Oid"