{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Language.GraphQL.Execute.Coerce
( Output(..)
, Serialize(..)
, VariableValue(..)
, coerceInputLiteral
, matchFieldValues
) where
import qualified Data.Aeson as Aeson
import Data.Int (Int32)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Map.Strict (Map)
import Data.String (IsString(..))
import Data.Text (Text)
import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Text.Lazy.Builder as Text.Builder
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
import Data.Scientific (toBoundedInteger, toRealFloat)
import Language.GraphQL.AST (Name)
import qualified Language.GraphQL.Type as Type
import qualified Language.GraphQL.Type.In as In
import qualified Language.GraphQL.Type.Out as Out
class VariableValue a where
coerceVariableValue
:: In.Type
-> a
-> Maybe Type.Value
instance VariableValue Aeson.Value where
coerceVariableValue :: Type -> Value -> Maybe Value
coerceVariableValue Type
_ Value
Aeson.Null = Value -> Maybe Value
forall a. a -> Maybe a
Just Value
Type.Null
coerceVariableValue (In.ScalarBaseType ScalarType
scalarType) Value
value
| (Aeson.String Text
stringValue) <- Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Type.String Text
stringValue
| (Aeson.Bool Bool
booleanValue) <- Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Type.Boolean Bool
booleanValue
| (Aeson.Number Scientific
numberValue) <- Value
value
, (Type.ScalarType Text
"Float" Maybe Text
_) <- ScalarType
scalarType =
Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Double -> Value
Type.Float (Double -> Value) -> Double -> Value
forall a b. (a -> b) -> a -> b
$ Scientific -> Double
forall a. RealFloat a => Scientific -> a
toRealFloat Scientific
numberValue
| (Aeson.Number Scientific
numberValue) <- Value
value =
Int32 -> Value
Type.Int (Int32 -> Value) -> Maybe Int32 -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Scientific -> Maybe Int32
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger Scientific
numberValue
coerceVariableValue (In.EnumBaseType EnumType
_) (Aeson.String Text
stringValue) =
Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Type.Enum Text
stringValue
coerceVariableValue (In.InputObjectBaseType InputObjectType
objectType) Value
value
| (Aeson.Object Object
objectValue) <- Value
value = do
let (In.InputObjectType Text
_ Maybe Text
_ HashMap Text InputField
inputFields) = InputObjectType
objectType
(Object
newObjectValue, HashMap Text Value
resultMap) <- Object
-> HashMap Text InputField -> Maybe (Object, HashMap Text Value)
forall v k.
(VariableValue v, Eq k, Hashable k) =>
HashMap k v
-> HashMap k InputField -> Maybe (HashMap k v, HashMap k Value)
foldWithKey Object
objectValue HashMap Text InputField
inputFields
if Object -> Bool
forall k v. HashMap k v -> Bool
HashMap.null Object
newObjectValue
then Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ HashMap Text Value -> Value
Type.Object HashMap Text Value
resultMap
else Maybe Value
forall a. Maybe a
Nothing
where
foldWithKey :: HashMap k v
-> HashMap k InputField -> Maybe (HashMap k v, HashMap k Value)
foldWithKey HashMap k v
objectValue = (k
-> InputField
-> Maybe (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value))
-> Maybe (HashMap k v, HashMap k Value)
-> HashMap k InputField
-> Maybe (HashMap k v, HashMap k Value)
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HashMap.foldrWithKey k
-> InputField
-> Maybe (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
forall k v.
(VariableValue v, Eq k, Hashable k) =>
k
-> InputField
-> Maybe (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
matchFieldValues'
(Maybe (HashMap k v, HashMap k Value)
-> HashMap k InputField -> Maybe (HashMap k v, HashMap k Value))
-> Maybe (HashMap k v, HashMap k Value)
-> HashMap k InputField
-> Maybe (HashMap k v, HashMap k Value)
forall a b. (a -> b) -> a -> b
$ (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
forall a. a -> Maybe a
Just (HashMap k v
objectValue, HashMap k Value
forall k v. HashMap k v
HashMap.empty)
matchFieldValues' :: k
-> InputField
-> Maybe (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
matchFieldValues' k
_ InputField
_ Maybe (HashMap k v, HashMap k Value)
Nothing = Maybe (HashMap k v, HashMap k Value)
forall a. Maybe a
Nothing
matchFieldValues' k
fieldName InputField
inputField (Just (HashMap k v
objectValue, HashMap k Value
resultMap)) =
let (In.InputField Maybe Text
_ Type
fieldType Maybe Value
_) = InputField
inputField
insert :: Value -> HashMap k Value
insert = (Value -> HashMap k Value -> HashMap k Value)
-> HashMap k Value -> Value -> HashMap k Value
forall a b c. (a -> b -> c) -> b -> a -> c
flip (k -> Value -> HashMap k Value -> HashMap k Value
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert k
fieldName) HashMap k Value
resultMap
newObjectValue :: HashMap k v
newObjectValue = k -> HashMap k v -> HashMap k v
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HashMap.delete k
fieldName HashMap k v
objectValue
in case k -> HashMap k v -> Maybe v
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup k
fieldName HashMap k v
objectValue of
Just v
variableValue -> do
Value
coerced <- Type -> v -> Maybe Value
forall a. VariableValue a => Type -> a -> Maybe Value
coerceVariableValue Type
fieldType v
variableValue
(HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HashMap k v
newObjectValue, Value -> HashMap k Value
insert Value
coerced)
Maybe v
Nothing -> (HashMap k v, HashMap k Value)
-> Maybe (HashMap k v, HashMap k Value)
forall a. a -> Maybe a
Just (HashMap k v
objectValue, HashMap k Value
resultMap)
coerceVariableValue (In.ListBaseType Type
listType) Value
value
| (Aeson.Array Array
arrayValue) <- Value
value =
[Value] -> Value
Type.List ([Value] -> Value) -> Maybe [Value] -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Maybe [Value] -> Maybe [Value])
-> Maybe [Value] -> Array -> Maybe [Value]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Value -> Maybe [Value] -> Maybe [Value]
forall a. VariableValue a => a -> Maybe [Value] -> Maybe [Value]
foldVector ([Value] -> Maybe [Value]
forall a. a -> Maybe a
Just []) Array
arrayValue
| Bool
otherwise = Type -> Value -> Maybe Value
forall a. VariableValue a => Type -> a -> Maybe Value
coerceVariableValue Type
listType Value
value
where
foldVector :: a -> Maybe [Value] -> Maybe [Value]
foldVector a
_ Maybe [Value]
Nothing = Maybe [Value]
forall a. Maybe a
Nothing
foldVector a
variableValue (Just [Value]
list) = do
Value
coerced <- Type -> a -> Maybe Value
forall a. VariableValue a => Type -> a -> Maybe Value
coerceVariableValue Type
listType a
variableValue
[Value] -> Maybe [Value]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Value] -> Maybe [Value]) -> [Value] -> Maybe [Value]
forall a b. (a -> b) -> a -> b
$ Value
coerced Value -> [Value] -> [Value]
forall a. a -> [a] -> [a]
: [Value]
list
coerceVariableValue Type
_ Value
_ = Maybe Value
forall a. Maybe a
Nothing
matchFieldValues :: forall a
. (In.Type -> a -> Maybe Type.Value)
-> HashMap Name a
-> Name
-> In.Type
-> Maybe Type.Value
-> Maybe (HashMap Name Type.Value)
-> Maybe (HashMap Name Type.Value)
matchFieldValues :: (Type -> a -> Maybe Value)
-> HashMap Text a
-> Text
-> Type
-> Maybe Value
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value)
matchFieldValues Type -> a -> Maybe Value
coerce HashMap Text a
values' Text
fieldName Type
type' Maybe Value
defaultValue Maybe (HashMap Text Value)
resultMap =
case Text -> HashMap Text a -> Maybe a
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
fieldName HashMap Text a
values' of
Just a
variableValue -> Maybe Value -> Maybe (HashMap Text Value)
coerceRuntimeValue (Maybe Value -> Maybe (HashMap Text Value))
-> Maybe Value -> Maybe (HashMap Text Value)
forall a b. (a -> b) -> a -> b
$ Type -> a -> Maybe Value
coerce Type
type' a
variableValue
Maybe a
Nothing
| Just Value
value <- Maybe Value
defaultValue ->
Text -> Value -> HashMap Text Value -> HashMap Text Value
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Text
fieldName Value
value (HashMap Text Value -> HashMap Text Value)
-> Maybe (HashMap Text Value) -> Maybe (HashMap Text Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (HashMap Text Value)
resultMap
| Maybe Value
Nothing <- Maybe Value
defaultValue
, Type -> Bool
In.isNonNullType Type
type' -> Maybe (HashMap Text Value)
forall a. Maybe a
Nothing
| Bool
otherwise -> Maybe (HashMap Text Value)
resultMap
where
coerceRuntimeValue :: Maybe Value -> Maybe (HashMap Text Value)
coerceRuntimeValue (Just Value
Type.Null)
| Type -> Bool
In.isNonNullType Type
type' = Maybe (HashMap Text Value)
forall a. Maybe a
Nothing
coerceRuntimeValue Maybe Value
coercedValue =
Text -> Value -> HashMap Text Value -> HashMap Text Value
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Text
fieldName (Value -> HashMap Text Value -> HashMap Text Value)
-> Maybe Value -> Maybe (HashMap Text Value -> HashMap Text Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Value
coercedValue Maybe (HashMap Text Value -> HashMap Text Value)
-> Maybe (HashMap Text Value) -> Maybe (HashMap Text Value)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe (HashMap Text Value)
resultMap
coerceInputLiteral :: In.Type -> Type.Value -> Maybe Type.Value
coerceInputLiteral :: Type -> Value -> Maybe Value
coerceInputLiteral (Type -> Bool
In.isNonNullType -> Bool
False) Value
Type.Null = Value -> Maybe Value
forall a. a -> Maybe a
Just Value
Type.Null
coerceInputLiteral (In.ScalarBaseType ScalarType
type') Value
value
| (Type.String Text
stringValue) <- Value
value
, (Type.ScalarType Text
"String" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Type.String Text
stringValue
| (Type.Boolean Bool
booleanValue) <- Value
value
, (Type.ScalarType Text
"Boolean" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Type.Boolean Bool
booleanValue
| (Type.Int Int32
intValue) <- Value
value
, (Type.ScalarType Text
"Int" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Value
Type.Int Int32
intValue
| (Type.Float Double
floatValue) <- Value
value
, (Type.ScalarType Text
"Float" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Double -> Value
Type.Float Double
floatValue
| (Type.Int Int32
intValue) <- Value
value
, (Type.ScalarType Text
"Float" Maybe Text
_) <- ScalarType
type' =
Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Double -> Value
Type.Float (Double -> Value) -> Double -> Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
intValue
| (Type.String Text
stringValue) <- Value
value
, (Type.ScalarType Text
"ID" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Type.String Text
stringValue
| (Type.Int Int32
intValue) <- Value
value
, (Type.ScalarType Text
"ID" Maybe Text
_) <- ScalarType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Value
decimal Int32
intValue
where
decimal :: Int32 -> Value
decimal = Text -> Value
Type.String
(Text -> Value) -> (Int32 -> Text) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.Lazy.toStrict
(Text -> Text) -> (Int32 -> Text) -> Int32 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Text.Builder.toLazyText
(Builder -> Text) -> (Int32 -> Builder) -> Int32 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Builder
forall a. Integral a => a -> Builder
Text.Builder.decimal
coerceInputLiteral (In.EnumBaseType EnumType
type') (Type.Enum Text
enumValue)
| Text -> EnumType -> Bool
member Text
enumValue EnumType
type' = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Type.Enum Text
enumValue
where
member :: Text -> EnumType -> Bool
member Text
value (Type.EnumType Text
_ Maybe Text
_ HashMap Text EnumValue
members) = Text -> HashMap Text EnumValue -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HashMap.member Text
value HashMap Text EnumValue
members
coerceInputLiteral (In.InputObjectBaseType InputObjectType
type') (Type.Object HashMap Text Value
values) =
let (In.InputObjectType Text
_ Maybe Text
_ HashMap Text InputField
inputFields) = InputObjectType
type'
in HashMap Text Value -> Value
Type.Object
(HashMap Text Value -> Value)
-> Maybe (HashMap Text Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
-> InputField
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value))
-> Maybe (HashMap Text Value)
-> HashMap Text InputField
-> Maybe (HashMap Text Value)
forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HashMap.foldrWithKey (HashMap Text Value
-> Text
-> InputField
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value)
matchFieldValues' HashMap Text Value
values) (HashMap Text Value -> Maybe (HashMap Text Value)
forall a. a -> Maybe a
Just HashMap Text Value
forall k v. HashMap k v
HashMap.empty) HashMap Text InputField
inputFields
where
matchFieldValues' :: HashMap Text Value
-> Text
-> InputField
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value)
matchFieldValues' HashMap Text Value
values' Text
fieldName (In.InputField Maybe Text
_ Type
inputFieldType Maybe Value
defaultValue) =
(Type -> Value -> Maybe Value)
-> HashMap Text Value
-> Text
-> Type
-> Maybe Value
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value)
forall a.
(Type -> a -> Maybe Value)
-> HashMap Text a
-> Text
-> Type
-> Maybe Value
-> Maybe (HashMap Text Value)
-> Maybe (HashMap Text Value)
matchFieldValues Type -> Value -> Maybe Value
coerceInputLiteral HashMap Text Value
values' Text
fieldName Type
inputFieldType Maybe Value
defaultValue
coerceInputLiteral (In.ListBaseType Type
listType) (Type.List [Value]
list) =
[Value] -> Value
Type.List ([Value] -> Value) -> Maybe [Value] -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Maybe Value) -> [Value] -> Maybe [Value]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Type -> Value -> Maybe Value
coerceInputLiteral Type
listType) [Value]
list
coerceInputLiteral (In.ListBaseType Type
listType) Value
singleton =
Type -> Value -> Maybe Value
wrapSingleton Type
listType Value
singleton
where
wrapSingleton :: Type -> Value -> Maybe Value
wrapSingleton (In.ListBaseType Type
listType') Value
singleton' =
[Value] -> Value
Type.List ([Value] -> Value) -> Maybe [Value] -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Maybe Value] -> Maybe [Value]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Type -> Value -> Maybe Value
wrapSingleton Type
listType' Value
singleton']
wrapSingleton Type
listType' Value
singleton' =
[Value] -> Value
Type.List ([Value] -> Value) -> Maybe [Value] -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Maybe Value] -> Maybe [Value]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Type -> Value -> Maybe Value
coerceInputLiteral Type
listType' Value
singleton']
coerceInputLiteral Type
_ Value
_ = Maybe Value
forall a. Maybe a
Nothing
class Serialize a where
serialize :: forall m
. Out.Type m
-> Output a
-> Maybe a
null :: a
data Output a
= Int Int32
| Float Double
| String Text
| Boolean Bool
| Enum Name
| List [a]
| Object (Map Name a)
deriving (Output a -> Output a -> Bool
(Output a -> Output a -> Bool)
-> (Output a -> Output a -> Bool) -> Eq (Output a)
forall a. Eq a => Output a -> Output a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Output a -> Output a -> Bool
$c/= :: forall a. Eq a => Output a -> Output a -> Bool
== :: Output a -> Output a -> Bool
$c== :: forall a. Eq a => Output a -> Output a -> Bool
Eq, Int -> Output a -> ShowS
[Output a] -> ShowS
Output a -> String
(Int -> Output a -> ShowS)
-> (Output a -> String) -> ([Output a] -> ShowS) -> Show (Output a)
forall a. Show a => Int -> Output a -> ShowS
forall a. Show a => [Output a] -> ShowS
forall a. Show a => Output a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Output a] -> ShowS
$cshowList :: forall a. Show a => [Output a] -> ShowS
show :: Output a -> String
$cshow :: forall a. Show a => Output a -> String
showsPrec :: Int -> Output a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Output a -> ShowS
Show)
instance forall a. IsString (Output a) where
fromString :: String -> Output a
fromString = Text -> Output a
forall a. Text -> Output a
String (Text -> Output a) -> (String -> Text) -> String -> Output a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString
instance Serialize Aeson.Value where
serialize :: Type m -> Output Value -> Maybe Value
serialize (Out.ScalarBaseType ScalarType
scalarType) Output Value
value
| Type.ScalarType Text
"Int" Maybe Text
_ <- ScalarType
scalarType
, Int Int32
int <- Output Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Int32 -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Int32
int
| Type.ScalarType Text
"Float" Maybe Text
_ <- ScalarType
scalarType
, Float Double
float <- Output Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Double -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Double
float
| Type.ScalarType Text
"String" Maybe Text
_ <- ScalarType
scalarType
, String Text
string <- Output Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Aeson.String Text
string
| Type.ScalarType Text
"ID" Maybe Text
_ <- ScalarType
scalarType
, String Text
string <- Output Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Aeson.String Text
string
| Type.ScalarType Text
"Boolean" Maybe Text
_ <- ScalarType
scalarType
, Boolean Bool
boolean <- Output Value
value = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Aeson.Bool Bool
boolean
serialize Type m
_ (Enum Text
enum) = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
Aeson.String Text
enum
serialize Type m
_ (List [Value]
list) = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON [Value]
list
serialize Type m
_ (Object Map Text Value
object) = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Map Text Value -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Map Text Value
object
serialize Type m
_ Output Value
_ = Maybe Value
forall a. Maybe a
Nothing
null :: Value
null = Value
Aeson.Null