Add description to the enum type values
This commit is contained in:
parent
4c9264c12c
commit
377c87045e
@ -55,6 +55,7 @@ and this project adheres to
|
|||||||
made private. These types describe intermediate representation used by the
|
made private. These types describe intermediate representation used by the
|
||||||
executor internally. Moving was required to avoid cyclic dependencies between
|
executor internally. Moving was required to avoid cyclic dependencies between
|
||||||
the executor and type system.
|
the executor and type system.
|
||||||
|
- `AST.Core` doesn't reexports anything.
|
||||||
|
|
||||||
## [0.7.0.0] - 2020-05-11
|
## [0.7.0.0] - 2020-05-11
|
||||||
### Fixed
|
### Fixed
|
||||||
|
@ -1,7 +1,6 @@
|
|||||||
-- | This is the AST meant to be executed.
|
-- | This is the AST meant to be executed.
|
||||||
module Language.GraphQL.AST.Core
|
module Language.GraphQL.AST.Core
|
||||||
( Arguments(..)
|
( Arguments(..)
|
||||||
, Name
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.HashMap.Strict (HashMap)
|
import Data.HashMap.Strict (HashMap)
|
||||||
|
@ -14,9 +14,8 @@ import qualified Data.HashMap.Strict as HashMap
|
|||||||
import qualified Data.Text.Lazy as Text.Lazy
|
import qualified Data.Text.Lazy as Text.Lazy
|
||||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||||
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
||||||
import qualified Data.Set as Set
|
|
||||||
import Data.Scientific (toBoundedInteger, toRealFloat)
|
import Data.Scientific (toBoundedInteger, toRealFloat)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST (Name)
|
||||||
import qualified Language.GraphQL.Type.In as In
|
import qualified Language.GraphQL.Type.In as In
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
|
|
||||||
@ -147,7 +146,7 @@ coerceInputLiteral (In.ScalarBaseType type') value
|
|||||||
coerceInputLiteral (In.EnumBaseType type') (Enum enumValue)
|
coerceInputLiteral (In.EnumBaseType type') (Enum enumValue)
|
||||||
| member enumValue type' = Just $ Enum enumValue
|
| member enumValue type' = Just $ Enum enumValue
|
||||||
where
|
where
|
||||||
member value (EnumType _ _ members) = Set.member value members
|
member value (EnumType _ _ members) = HashMap.member value members
|
||||||
coerceInputLiteral (In.InputObjectBaseType type') (Object values) =
|
coerceInputLiteral (In.InputObjectBaseType type') (Object values) =
|
||||||
let (In.InputObjectType _ _ inputFields) = type'
|
let (In.InputObjectType _ _ inputFields) = type'
|
||||||
in Object
|
in Object
|
||||||
|
@ -19,6 +19,7 @@ import Data.Sequence (Seq(..))
|
|||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import qualified Data.Sequence as Seq
|
import qualified Data.Sequence as Seq
|
||||||
|
import Language.GraphQL.AST (Name)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST.Core
|
||||||
import Language.GraphQL.Error
|
import Language.GraphQL.Error
|
||||||
import Language.GraphQL.Execute.Coerce
|
import Language.GraphQL.Execute.Coerce
|
||||||
|
@ -43,6 +43,7 @@ import Data.Sequence (Seq, (<|), (><))
|
|||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import qualified Language.GraphQL.AST as Full
|
import qualified Language.GraphQL.AST as Full
|
||||||
|
import Language.GraphQL.AST (Name)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST.Core
|
||||||
import Language.GraphQL.Execute.Coerce
|
import Language.GraphQL.Execute.Coerce
|
||||||
import Language.GraphQL.Type.Directive (Directive(..))
|
import Language.GraphQL.Type.Directive (Directive(..))
|
||||||
|
@ -14,6 +14,7 @@ import Control.Monad.Trans.Reader (ReaderT, asks)
|
|||||||
import qualified Data.HashMap.Strict as HashMap
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
import Language.GraphQL.AST (Name)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST.Core
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
import Prelude hiding (lookup)
|
import Prelude hiding (lookup)
|
||||||
|
@ -3,6 +3,7 @@
|
|||||||
-- | Types that can be used as both input and output types.
|
-- | Types that can be used as both input and output types.
|
||||||
module Language.GraphQL.Type.Definition
|
module Language.GraphQL.Type.Definition
|
||||||
( EnumType(..)
|
( EnumType(..)
|
||||||
|
, EnumValue(..)
|
||||||
, ScalarType(..)
|
, ScalarType(..)
|
||||||
, Subs
|
, Subs
|
||||||
, Value(..)
|
, Value(..)
|
||||||
@ -15,7 +16,6 @@ module Language.GraphQL.Type.Definition
|
|||||||
|
|
||||||
import Data.Int (Int32)
|
import Data.Int (Int32)
|
||||||
import Data.HashMap.Strict (HashMap)
|
import Data.HashMap.Strict (HashMap)
|
||||||
import Data.Set (Set)
|
|
||||||
import Data.String (IsString(..))
|
import Data.String (IsString(..))
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Language.GraphQL.AST.Document (Name)
|
import Language.GraphQL.AST.Document (Name)
|
||||||
@ -51,7 +51,10 @@ data ScalarType = ScalarType Name (Maybe Text)
|
|||||||
-- Some leaf values of requests and input values are Enums. GraphQL serializes
|
-- Some leaf values of requests and input values are Enums. GraphQL serializes
|
||||||
-- Enum values as strings, however internally Enums can be represented by any
|
-- Enum values as strings, however internally Enums can be represented by any
|
||||||
-- kind of type, often integers.
|
-- kind of type, often integers.
|
||||||
data EnumType = EnumType Name (Maybe Text) (Set Text)
|
data EnumType = EnumType Name (Maybe Text) (HashMap Name EnumValue)
|
||||||
|
|
||||||
|
-- | Enum value is a single member of an 'EnumType'.
|
||||||
|
newtype EnumValue = EnumValue (Maybe Text)
|
||||||
|
|
||||||
-- | The @String@ scalar type represents textual data, represented as UTF-8
|
-- | The @String@ scalar type represents textual data, represented as UTF-8
|
||||||
-- character sequences. The String type is most often used by GraphQL to
|
-- character sequences. The String type is most often used by GraphQL to
|
||||||
|
@ -6,6 +6,7 @@ module Language.GraphQL.Type.Directive
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.HashMap.Strict as HashMap
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
|
import Language.GraphQL.AST (Name)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST.Core
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
|
|
||||||
|
@ -24,7 +24,7 @@ module Language.GraphQL.Type.Out
|
|||||||
|
|
||||||
import Data.HashMap.Strict (HashMap)
|
import Data.HashMap.Strict (HashMap)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Language.GraphQL.AST.Core
|
import Language.GraphQL.AST (Name)
|
||||||
import Language.GraphQL.Trans
|
import Language.GraphQL.Trans
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
import qualified Language.GraphQL.Type.In as In
|
import qualified Language.GraphQL.Type.In as In
|
||||||
|
@ -9,7 +9,6 @@ import qualified Data.Aeson.Types as Aeson
|
|||||||
import qualified Data.HashMap.Strict as HashMap
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
import Data.Maybe (isNothing)
|
import Data.Maybe (isNothing)
|
||||||
import Data.Scientific (scientific)
|
import Data.Scientific (scientific)
|
||||||
import qualified Data.Set as Set
|
|
||||||
import Language.GraphQL.Execute.Coerce
|
import Language.GraphQL.Execute.Coerce
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
import qualified Language.GraphQL.Type.In as In
|
import qualified Language.GraphQL.Type.In as In
|
||||||
@ -17,8 +16,12 @@ import Prelude hiding (id)
|
|||||||
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
|
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
|
||||||
|
|
||||||
direction :: EnumType
|
direction :: EnumType
|
||||||
direction = EnumType "Direction" Nothing
|
direction = EnumType "Direction" Nothing $ HashMap.fromList
|
||||||
$ Set.fromList ["NORTH", "EAST", "SOUTH", "WEST"]
|
[ ("NORTH", EnumValue Nothing)
|
||||||
|
, ("EAST", EnumValue Nothing)
|
||||||
|
, ("SOUTH", EnumValue Nothing)
|
||||||
|
, ("WEST", EnumValue Nothing)
|
||||||
|
]
|
||||||
|
|
||||||
singletonInputObject :: In.Type
|
singletonInputObject :: In.Type
|
||||||
singletonInputObject = In.NamedInputObjectType type'
|
singletonInputObject = In.NamedInputObjectType type'
|
||||||
|
@ -11,7 +11,6 @@ import Data.Functor.Identity (Identity)
|
|||||||
import qualified Data.HashMap.Strict as HashMap
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
import Data.Maybe (catMaybes)
|
import Data.Maybe (catMaybes)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Set as Set
|
|
||||||
import Language.GraphQL.Trans
|
import Language.GraphQL.Trans
|
||||||
import Language.GraphQL.Type.Definition
|
import Language.GraphQL.Type.Definition
|
||||||
import qualified Language.GraphQL.Type.In as In
|
import qualified Language.GraphQL.Type.In as In
|
||||||
@ -86,8 +85,13 @@ idField f = do
|
|||||||
pure $ v' HashMap.! f
|
pure $ v' HashMap.! f
|
||||||
|
|
||||||
episodeEnum :: EnumType
|
episodeEnum :: EnumType
|
||||||
episodeEnum = EnumType "Episode" Nothing
|
episodeEnum = EnumType "Episode" (Just description)
|
||||||
$ Set.fromList ["NEW_HOPE", "EMPIRE", "JEDI"]
|
$ HashMap.fromList [newHope, empire, jedi]
|
||||||
|
where
|
||||||
|
description = "One of the films in the Star Wars Trilogy"
|
||||||
|
newHope = ("NEW_HOPE", EnumValue $ Just "Released in 1977.")
|
||||||
|
empire = ("EMPIRE", EnumValue $ Just "Released in 1980.")
|
||||||
|
jedi = ("JEDI", EnumValue $ Just "Released in 1983.")
|
||||||
|
|
||||||
hero :: ActionT Identity Value
|
hero :: ActionT Identity Value
|
||||||
hero = do
|
hero = do
|
||||||
|
Loading…
Reference in New Issue
Block a user