{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_HADDOCK not-home #-}
module GraphQL.Internal.Value.ToValue
( ToValue(..)
) where
import Protolude
import GraphQL.Internal.Value
class ToValue a where
toValue :: a -> Value' ConstScalar
instance ToValue (Value' ConstScalar) where
toValue = identity
instance ToValue a => ToValue [a] where
toValue = toValue . List' . map toValue
instance ToValue a => ToValue (Maybe a) where
toValue Nothing = ValueNull
toValue (Just v) = toValue v
instance ToValue a => ToValue (NonEmpty a) where
toValue = toValue . makeList
instance ToValue Bool where
toValue = ValueBoolean
instance ToValue Int32 where
toValue = ValueInt
instance ToValue Double where
toValue = ValueFloat
instance ToValue String where
toValue = ValueString
instance ToValue Text where
toValue = toValue . String
instance ToValue List where
toValue = ValueList'
instance ToValue (Object' ConstScalar) where
toValue = ValueObject'
makeList :: (Functor f, Foldable f, ToValue a) => f a -> List
makeList = List' . Protolude.toList . map toValue