| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GraphQL.Internal.Value
Description
Synopsis
- type Value = Value' ConstScalar
- data Value' scalar- = ValueScalar' scalar
- | ValueList' (List' scalar)
- | ValueObject' (Object' scalar)
 
- data ConstScalar
- type UnresolvedVariableValue = Value' UnresolvedVariableScalar
- pattern ValueInt :: Int32 -> Value
- pattern ValueFloat :: Double -> Value
- pattern ValueBoolean :: Bool -> Value
- pattern ValueString :: String -> Value
- pattern ValueEnum :: Name -> Value
- pattern ValueList :: forall t. List' t -> Value' t
- pattern ValueObject :: forall t. Object' t -> Value' t
- pattern ValueNull :: Value
- toObject :: Value' scalar -> Maybe (Object' scalar)
- valueToAST :: Value -> Value
- astToVariableValue :: HasCallStack => Value -> Maybe UnresolvedVariableValue
- variableValueToAST :: UnresolvedVariableValue -> Value
- type List = List' ConstScalar
- newtype List' scalar = List' [Value' scalar]
- newtype String = String Text
- newtype Name = Name {}
- newtype NameError = NameError Text
- makeName :: Text -> Either NameError Name
- type Object = Object' ConstScalar
- newtype Object' scalar = Object' (OrderedMap Name (Value' scalar))
- type ObjectField = ObjectField' ConstScalar
- data ObjectField' scalar where- pattern ObjectField :: forall t. Name -> Value' t -> ObjectField' t
 
- makeObject :: [ObjectField' scalar] -> Maybe (Object' scalar)
- objectFromList :: [(Name, Value' scalar)] -> Maybe (Object' scalar)
- objectFromOrderedMap :: OrderedMap Name (Value' scalar) -> Object' scalar
- unionObjects :: [Object' scalar] -> Maybe (Object' scalar)
- objectFields :: Object' scalar -> [ObjectField' scalar]
Documentation
type Value = Value' ConstScalar Source #
A GraphQL value which contains no variables.
A GraphQL value. scalar represents the type of scalar that's contained
 within this value.
Normally, it is one of either ConstScalar (to indicate that there are no
 variables whatsoever) or VariableScalar (to indicate that there might be
 some variables).
Constructors
| ValueScalar' scalar | |
| ValueList' (List' scalar) | |
| ValueObject' (Object' scalar) | 
Instances
| Functor Value' Source # | |
| Foldable Value' Source # | |
| Defined in GraphQL.Internal.Value Methods fold :: Monoid m => Value' m -> m # foldMap :: Monoid m => (a -> m) -> Value' a -> m # foldr :: (a -> b -> b) -> b -> Value' a -> b # foldr' :: (a -> b -> b) -> b -> Value' a -> b # foldl :: (b -> a -> b) -> b -> Value' a -> b # foldl' :: (b -> a -> b) -> b -> Value' a -> b # foldr1 :: (a -> a -> a) -> Value' a -> a # foldl1 :: (a -> a -> a) -> Value' a -> a # elem :: Eq a => a -> Value' a -> Bool # maximum :: Ord a => Value' a -> a # minimum :: Ord a => Value' a -> a # | |
| Traversable Value' Source # | |
| Eq scalar => Eq (Value' scalar) Source # | |
| Ord scalar => Ord (Value' scalar) Source # | |
| Defined in GraphQL.Internal.Value Methods compare :: Value' scalar -> Value' scalar -> Ordering # (<) :: Value' scalar -> Value' scalar -> Bool # (<=) :: Value' scalar -> Value' scalar -> Bool # (>) :: Value' scalar -> Value' scalar -> Bool # (>=) :: Value' scalar -> Value' scalar -> Bool # | |
| Show scalar => Show (Value' scalar) Source # | |
| Arbitrary scalar => Arbitrary (Value' scalar) Source # | |
| ToJSON scalar => ToJSON (Value' scalar) Source # | |
| Defined in GraphQL.Internal.Value | |
| ToValue (Value' ConstScalar) Source # | |
| Defined in GraphQL.Internal.Value.ToValue Methods toValue :: Value' ConstScalar -> Value' ConstScalar Source # | |
data ConstScalar Source #
A non-variable value which contains no other values.
Instances
type UnresolvedVariableValue = Value' UnresolvedVariableScalar Source #
A GraphQL value which might contain some variables. These variables are
 not yet associated with
 <https://facebook.github.io/graphql/#VariableDefinition variable
 definitions> (see also VariableDefinition),
 which are provided in a different context.
pattern ValueFloat :: Double -> Value Source #
pattern ValueBoolean :: Bool -> Value Source #
pattern ValueString :: String -> Value Source #
pattern ValueObject :: forall t. Object' t -> Value' t Source #
toObject :: Value' scalar -> Maybe (Object' scalar) Source #
If a value is an object, return just that. Otherwise Nothing.
valueToAST :: Value -> Value Source #
Convert a value to an AST value.
astToVariableValue :: HasCallStack => Value -> Maybe UnresolvedVariableValue Source #
Convert an AST value to a variable value.
Will fail if the AST value contains duplicate object fields, or is otherwise invalid.
variableValueToAST :: UnresolvedVariableValue -> Value Source #
Convert a variable value to an AST value.
type List = List' ConstScalar Source #
A list of values that are known to be constants.
Note that this list might not be valid GraphQL, because GraphQL only allows homogeneous lists (i.e. all elements of the same type), and we do no type checking at this point.
Instances
| Functor List' Source # | |
| Foldable List' Source # | |
| Defined in GraphQL.Internal.Value Methods fold :: Monoid m => List' m -> m # foldMap :: Monoid m => (a -> m) -> List' a -> m # foldr :: (a -> b -> b) -> b -> List' a -> b # foldr' :: (a -> b -> b) -> b -> List' a -> b # foldl :: (b -> a -> b) -> b -> List' a -> b # foldl' :: (b -> a -> b) -> b -> List' a -> b # foldr1 :: (a -> a -> a) -> List' a -> a # foldl1 :: (a -> a -> a) -> List' a -> a # elem :: Eq a => a -> List' a -> Bool # maximum :: Ord a => List' a -> a # minimum :: Ord a => List' a -> a # | |
| Traversable List' Source # | |
| ToValue List Source # | |
| Defined in GraphQL.Internal.Value.ToValue | |
| Eq scalar => Eq (List' scalar) Source # | |
| Ord scalar => Ord (List' scalar) Source # | |
| Defined in GraphQL.Internal.Value | |
| Show scalar => Show (List' scalar) Source # | |
| Arbitrary scalar => Arbitrary (List' scalar) Source # | |
| ToJSON scalar => ToJSON (List' scalar) Source # | |
| Defined in GraphQL.Internal.Value | |
Names
A name in GraphQL.
An invalid name.
makeName :: Text -> Either NameError Name Source #
Create a Name.
Names must match the regex [_A-Za-z][_0-9A-Za-z]*. If the given text does
 not match, return NameError.
>>>makeName "foo"Right (Name {unName = "foo"})>>>makeName "9-bar"Left (NameError "9-bar")
Objects
type Object = Object' ConstScalar Source #
A GraphQL object that contains only non-variable values.
newtype Object' scalar Source #
A GraphQL object.
Note that https://facebook.github.io/graphql/#sec-Response calls these "Maps", but everywhere else in the spec refers to them as objects.
Constructors
| Object' (OrderedMap Name (Value' scalar)) | 
Instances
type ObjectField = ObjectField' ConstScalar Source #
A field of an object that has a non-variable value.
data ObjectField' scalar where Source #
Bundled Patterns
| pattern ObjectField :: forall t. Name -> Value' t -> ObjectField' t | 
Instances
Constructing
makeObject :: [ObjectField' scalar] -> Maybe (Object' scalar) Source #
Make an object from a list of object fields.
objectFromList :: [(Name, Value' scalar)] -> Maybe (Object' scalar) Source #
Create an object from a list of (name, value) pairs.
objectFromOrderedMap :: OrderedMap Name (Value' scalar) -> Object' scalar Source #
Make an object from an ordered map.
Combining
Querying
objectFields :: Object' scalar -> [ObjectField' scalar] Source #