{- This Source Code Form is subject to the terms of the Mozilla Public License,
   v. 2.0. If a copy of the MPL was not distributed with this file, You can
   obtain one at https://mozilla.org/MPL/2.0/. -}

{-# LANGUAGE OverloadedStrings #-}

-- | ToGraphQL and FromGraphQL typeclasses used for user-defined type
-- conversion.
module Language.GraphQL.Class
    ( FromGraphQL(..)
    , ToGraphQL(..)
    ) where

import Data.Foldable (toList)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Text (Text)
import Data.Word (Word8, Word16, Word32, Word64)
import qualified Data.Text.Read as Text.Read
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import qualified Language.GraphQL.Type as Type
import Data.Scientific (Scientific, toRealFloat)
import qualified Data.Text as Text
import Data.Time
    ( Day
    , DiffTime
    , LocalTime(..)
    , NominalDiffTime
    , TimeOfDay(..)
    , UTCTime(..)
    , showGregorian
    , secondsToNominalDiffTime
    , secondsToDiffTime
    )
import Data.Time.Format.ISO8601
    ( ISO8601(..)
    , formatParseM
    , iso8601Format
    , iso8601Show
    )

fromGraphQLToIntegral :: Integral a => Type.Value -> Maybe a
fromGraphQLToIntegral :: forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral (Type.Int Int32
value) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
value
fromGraphQLToIntegral (Type.String Text
value) =
    case forall a. Integral a => Reader a
Text.Read.decimal Text
value of
        Right (a
converted, Text
"") -> forall a. a -> Maybe a
Just a
converted
        Either String (a, Text)
_conversionError -> forall a. Maybe a
Nothing
fromGraphQLToIntegral Value
_ = forall a. Maybe a
Nothing

iso8601ToGraphQL :: ISO8601 t => t -> Type.Value
iso8601ToGraphQL :: forall t. ISO8601 t => t -> Value
iso8601ToGraphQL = Text -> Value
Type.String forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. ISO8601 t => t -> String
iso8601Show

fromGraphQLToISO8601 :: ISO8601 t => Type.Value -> Maybe t
fromGraphQLToISO8601 :: forall t. ISO8601 t => Value -> Maybe t
fromGraphQLToISO8601 (Type.String Text
value') = forall (m :: * -> *) t. MonadFail m => Format t -> String -> m t
formatParseM forall t. ISO8601 t => Format t
iso8601Format forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
value'
fromGraphQLToISO8601 Value
_ = forall a. Maybe a
Nothing

-- | Instances of this typeclass can be converted to GraphQL internal
-- representation.
class ToGraphQL a
  where
    toGraphQL :: a -> Type.Value

instance ToGraphQL Text
  where
    toGraphQL :: Text -> Value
toGraphQL = Text -> Value
Type.String

instance ToGraphQL Int
  where
    toGraphQL :: Int -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Int8
  where
    toGraphQL :: Int8 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Int16
  where
    toGraphQL :: Int16 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Int32
  where
    toGraphQL :: Int32 -> Value
toGraphQL = Int32 -> Value
Type.Int

instance ToGraphQL Int64
  where
    toGraphQL :: Int64 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Word
  where
    toGraphQL :: Word -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Word8
  where
    toGraphQL :: Word8 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Word16
  where
    toGraphQL :: Word16 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Word32
  where
    toGraphQL :: Word32 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL Word64
  where
    toGraphQL :: Word64 -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToGraphQL a => ToGraphQL [a]
  where
    toGraphQL :: [a] -> Value
toGraphQL = [Value] -> Value
Type.List forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. ToGraphQL a => a -> Value
toGraphQL

instance ToGraphQL a => ToGraphQL (Vector a)
  where
    toGraphQL :: Vector a -> Value
toGraphQL = [Value] -> Value
Type.List forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. ToGraphQL a => a -> Value
toGraphQL

instance ToGraphQL a => ToGraphQL (Maybe a)
  where
    toGraphQL :: Maybe a -> Value
toGraphQL (Just a
justValue) = forall a. ToGraphQL a => a -> Value
toGraphQL a
justValue
    toGraphQL Maybe a
Nothing = Value
Type.Null

instance ToGraphQL Bool
  where
    toGraphQL :: Bool -> Value
toGraphQL = Bool -> Value
Type.Boolean

instance ToGraphQL Float
  where
    toGraphQL :: Float -> Value
toGraphQL = Double -> Value
Type.Float forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac

instance ToGraphQL Double
  where
    toGraphQL :: Double -> Value
toGraphQL = Double -> Value
Type.Float

instance ToGraphQL Scientific
  where
    toGraphQL :: Scientific -> Value
toGraphQL = Double -> Value
Type.Float forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Scientific -> a
toRealFloat

instance ToGraphQL Day
  where
    toGraphQL :: Day -> Value
toGraphQL = Text -> Value
Type.String forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> String
showGregorian

instance ToGraphQL DiffTime
  where
    toGraphQL :: DiffTime -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (RealFrac a, Integral b) => a -> b
truncate forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: DiffTime -> Double)

instance ToGraphQL NominalDiffTime
  where
    toGraphQL :: NominalDiffTime -> Value
toGraphQL = Int32 -> Value
Type.Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (RealFrac a, Integral b) => a -> b
truncate forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: NominalDiffTime -> Double)

instance ToGraphQL UTCTime
  where
    toGraphQL :: UTCTime -> Value
toGraphQL = forall t. ISO8601 t => t -> Value
iso8601ToGraphQL

instance ToGraphQL TimeOfDay
  where
    toGraphQL :: TimeOfDay -> Value
toGraphQL = forall t. ISO8601 t => t -> Value
iso8601ToGraphQL

instance ToGraphQL LocalTime
  where
    toGraphQL :: LocalTime -> Value
toGraphQL = forall t. ISO8601 t => t -> Value
iso8601ToGraphQL

-- | Instances of this typeclass can be used to convert GraphQL internal
-- representation to user-defined type.
class FromGraphQL a
  where
    fromGraphQL :: Type.Value -> Maybe a

instance FromGraphQL Text
  where
    fromGraphQL :: Value -> Maybe Text
fromGraphQL (Type.String Text
value) = forall a. a -> Maybe a
Just Text
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL Int
  where
    fromGraphQL :: Value -> Maybe Int
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Int8
  where
    fromGraphQL :: Value -> Maybe Int8
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Int16
  where
    fromGraphQL :: Value -> Maybe Int16
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Int32
  where
    fromGraphQL :: Value -> Maybe Int32
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Int64
  where
    fromGraphQL :: Value -> Maybe Int64
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Word
  where
    fromGraphQL :: Value -> Maybe Word
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Word8
  where
    fromGraphQL :: Value -> Maybe Word8
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Word16
  where
    fromGraphQL :: Value -> Maybe Word16
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Word32
  where
    fromGraphQL :: Value -> Maybe Word32
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL Word64
  where
    fromGraphQL :: Value -> Maybe Word64
fromGraphQL = forall a. Integral a => Value -> Maybe a
fromGraphQLToIntegral

instance FromGraphQL a => FromGraphQL [a]
  where
    fromGraphQL :: Value -> Maybe [a]
fromGraphQL (Type.List [Value]
value) = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall a. FromGraphQL a => Value -> Maybe a
fromGraphQL [Value]
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL a => FromGraphQL (Vector a)
  where
    fromGraphQL :: Value -> Maybe (Vector a)
fromGraphQL (Type.List [Value]
value) = forall a. [a] -> Vector a
Vector.fromList
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall a. FromGraphQL a => Value -> Maybe a
fromGraphQL [Value]
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL a => FromGraphQL (Maybe a)
  where
    fromGraphQL :: Value -> Maybe (Maybe a)
fromGraphQL Value
Type.Null = forall a. a -> Maybe a
Just forall a. Maybe a
Nothing
    fromGraphQL Value
value = forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromGraphQL a => Value -> Maybe a
fromGraphQL Value
value

instance FromGraphQL Bool
  where
    fromGraphQL :: Value -> Maybe Bool
fromGraphQL (Type.Boolean Bool
value) = forall a. a -> Maybe a
Just Bool
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL Float
  where
    fromGraphQL :: Value -> Maybe Float
fromGraphQL (Type.Float Double
value) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL Double
  where
    fromGraphQL :: Value -> Maybe Double
fromGraphQL (Type.Float Double
value) = forall a. a -> Maybe a
Just Double
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL Scientific
  where
    fromGraphQL :: Value -> Maybe Scientific
fromGraphQL (Type.Float Double
value) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL Day
  where
    fromGraphQL :: Value -> Maybe Day
fromGraphQL = forall t. ISO8601 t => Value -> Maybe t
fromGraphQLToISO8601

instance FromGraphQL DiffTime
  where
    fromGraphQL :: Value -> Maybe DiffTime
fromGraphQL (Type.Int Int32
value') = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Integer -> DiffTime
secondsToDiffTime forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
value'
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL NominalDiffTime
  where
    fromGraphQL :: Value -> Maybe NominalDiffTime
fromGraphQL (Type.Int Int32
value') = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Pico -> NominalDiffTime
secondsToNominalDiffTime forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
value'
    fromGraphQL Value
_ = forall a. Maybe a
Nothing

instance FromGraphQL UTCTime
  where
    fromGraphQL :: Value -> Maybe UTCTime
fromGraphQL = forall t. ISO8601 t => Value -> Maybe t
fromGraphQLToISO8601

instance FromGraphQL TimeOfDay
  where
    fromGraphQL :: Value -> Maybe TimeOfDay
fromGraphQL = forall t. ISO8601 t => Value -> Maybe t
fromGraphQLToISO8601

instance FromGraphQL LocalTime
  where
    fromGraphQL :: Value -> Maybe LocalTime
fromGraphQL = forall t. ISO8601 t => Value -> Maybe t
fromGraphQLToISO8601