197 lines
4.5 KiB
Haskell
Raw Normal View History

{- 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
2023-06-23 17:31:19 +02:00
import Data.Scientific (Scientific, toRealFloat)
fromGraphQLToIntegral :: Integral a => Type.Value -> Maybe a
fromGraphQLToIntegral (Type.Int value) = Just $ fromIntegral value
fromGraphQLToIntegral (Type.String value) =
case Text.Read.decimal value of
Right (converted, "") -> Just converted
_conversionError -> Nothing
fromGraphQLToIntegral _ = Nothing
-- | Instances of this typeclass can be converted to GraphQL internal
-- representation.
2023-06-23 17:31:19 +02:00
class ToGraphQL a
where
toGraphQL :: a -> Type.Value
2023-06-23 17:31:19 +02:00
instance ToGraphQL Text
where
toGraphQL = Type.String
2023-06-23 17:31:19 +02:00
instance ToGraphQL Int
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Int8
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Int16
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Int32
where
toGraphQL = Type.Int
2023-06-23 17:31:19 +02:00
instance ToGraphQL Int64
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Word
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Word8
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Word16
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Word32
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL Word64
where
toGraphQL = Type.Int . fromIntegral
2023-06-23 17:31:19 +02:00
instance ToGraphQL a => ToGraphQL [a]
where
toGraphQL = Type.List . fmap toGraphQL
2023-06-23 17:31:19 +02:00
instance ToGraphQL a => ToGraphQL (Vector a)
where
toGraphQL = Type.List . toList . fmap toGraphQL
2023-06-23 17:31:19 +02:00
instance ToGraphQL a => ToGraphQL (Maybe a)
where
toGraphQL (Just justValue) = toGraphQL justValue
toGraphQL Nothing = Type.Null
2023-06-23 17:31:19 +02:00
instance ToGraphQL Bool
where
toGraphQL = Type.Boolean
2023-06-23 17:31:19 +02:00
instance ToGraphQL Float
where
2023-05-07 17:19:57 +02:00
toGraphQL = Type.Float . realToFrac
2023-06-23 17:31:19 +02:00
instance ToGraphQL Double
where
2023-05-07 17:19:57 +02:00
toGraphQL = Type.Float
2023-06-23 17:31:19 +02:00
instance ToGraphQL Scientific
where
toGraphQL = Type.Float . toRealFloat
-- | Instances of this typeclass can be used to convert GraphQL internal
-- representation to user-defined type.
2023-06-23 17:31:19 +02:00
class FromGraphQL a
where
fromGraphQL :: Type.Value -> Maybe a
2023-06-23 17:31:19 +02:00
instance FromGraphQL Text
where
fromGraphQL (Type.String value) = Just value
fromGraphQL _ = Nothing
2023-06-23 17:31:19 +02:00
instance FromGraphQL Int
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Int8
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Int16
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Int32
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Int64
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Word
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Word8
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Word16
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Word32
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL Word64
where
fromGraphQL = fromGraphQLToIntegral
2023-06-23 17:31:19 +02:00
instance FromGraphQL a => FromGraphQL [a]
where
fromGraphQL (Type.List value) = traverse fromGraphQL value
fromGraphQL _ = Nothing
2023-06-23 17:31:19 +02:00
instance FromGraphQL a => FromGraphQL (Vector a)
where
fromGraphQL (Type.List value) = Vector.fromList
<$> traverse fromGraphQL value
fromGraphQL _ = Nothing
2023-06-23 17:31:19 +02:00
instance FromGraphQL a => FromGraphQL (Maybe a)
where
fromGraphQL Type.Null = Just Nothing
fromGraphQL value = Just <$> fromGraphQL value
2023-06-23 17:31:19 +02:00
instance FromGraphQL Bool
where
fromGraphQL (Type.Boolean value) = Just value
fromGraphQL _ = Nothing
2023-05-07 17:19:57 +02:00
2023-06-23 17:31:19 +02:00
instance FromGraphQL Float
where
2023-05-07 17:19:57 +02:00
fromGraphQL (Type.Float value) = Just $ realToFrac value
fromGraphQL _ = Nothing
2023-06-23 17:31:19 +02:00
instance FromGraphQL Double
where
2023-05-07 17:19:57 +02:00
fromGraphQL (Type.Float value) = Just value
fromGraphQL _ = Nothing
2023-06-23 17:31:19 +02:00
instance FromGraphQL Scientific
where
fromGraphQL (Type.Float value) = Just $ realToFrac value
fromGraphQL _ = Nothing