graphql-api-0.4.0: GraphQL API

Safe HaskellNone
LanguageHaskell2010

GraphQL.Value

Contents

Description

 
Synopsis

Documentation

type Value = Value' ConstScalar Source #

A GraphQL value which contains no variables.

data Value' scalar Source #

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 # 
Instance details

Defined in GraphQL.Internal.Value

Methods

fmap :: (a -> b) -> Value' a -> Value' b #

(<$) :: a -> Value' b -> Value' a #

Foldable Value' Source # 
Instance details

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 #

toList :: Value' a -> [a] #

null :: Value' a -> Bool #

length :: Value' a -> Int #

elem :: Eq a => a -> Value' a -> Bool #

maximum :: Ord a => Value' a -> a #

minimum :: Ord a => Value' a -> a #

sum :: Num a => Value' a -> a #

product :: Num a => Value' a -> a #

Traversable Value' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

traverse :: Applicative f => (a -> f b) -> Value' a -> f (Value' b) #

sequenceA :: Applicative f => Value' (f a) -> f (Value' a) #

mapM :: Monad m => (a -> m b) -> Value' a -> m (Value' b) #

sequence :: Monad m => Value' (m a) -> m (Value' a) #

Eq scalar => Eq (Value' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

(==) :: Value' scalar -> Value' scalar -> Bool #

(/=) :: Value' scalar -> Value' scalar -> Bool #

Ord scalar => Ord (Value' scalar) Source # 
Instance details

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 #

max :: Value' scalar -> Value' scalar -> Value' scalar #

min :: Value' scalar -> Value' scalar -> Value' scalar #

Show scalar => Show (Value' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

showsPrec :: Int -> Value' scalar -> ShowS #

show :: Value' scalar -> String #

showList :: [Value' scalar] -> ShowS #

Arbitrary scalar => Arbitrary (Value' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

arbitrary :: Gen (Value' scalar) #

shrink :: Value' scalar -> [Value' scalar] #

ToJSON scalar => ToJSON (Value' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

toJSON :: Value' scalar -> Value #

toEncoding :: Value' scalar -> Encoding #

toJSONList :: [Value' scalar] -> Value #

toEncodingList :: [Value' scalar] -> Encoding #

ToValue (Value' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

data ConstScalar Source #

A non-variable value which contains no other values.

Instances
Eq ConstScalar Source # 
Instance details

Defined in GraphQL.Internal.Value

Ord ConstScalar Source # 
Instance details

Defined in GraphQL.Internal.Value

Show ConstScalar Source # 
Instance details

Defined in GraphQL.Internal.Value

Arbitrary ConstScalar Source #

Generate an arbitrary scalar value.

Instance details

Defined in GraphQL.Internal.Value

ToJSON ConstScalar Source # 
Instance details

Defined in GraphQL.Internal.Value

ToValue List Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue (Object' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue (Value' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

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 ValueInt :: Int32 -> Value Source #

pattern ValueEnum :: Name -> Value Source #

pattern ValueList :: forall t. List' t -> Value' t Source #

pattern ValueObject :: forall t. Object' t -> Value' t Source #

pattern ValueNull :: Value 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.

newtype List' scalar Source #

Constructors

List' [Value' scalar] 
Instances
Functor List' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

fmap :: (a -> b) -> List' a -> List' b #

(<$) :: a -> List' b -> List' a #

Foldable List' Source # 
Instance details

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 #

toList :: List' a -> [a] #

null :: List' a -> Bool #

length :: List' a -> Int #

elem :: Eq a => a -> List' a -> Bool #

maximum :: Ord a => List' a -> a #

minimum :: Ord a => List' a -> a #

sum :: Num a => List' a -> a #

product :: Num a => List' a -> a #

Traversable List' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

traverse :: Applicative f => (a -> f b) -> List' a -> f (List' b) #

sequenceA :: Applicative f => List' (f a) -> f (List' a) #

mapM :: Monad m => (a -> m b) -> List' a -> m (List' b) #

sequence :: Monad m => List' (m a) -> m (List' a) #

ToValue List Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

Eq scalar => Eq (List' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

(==) :: List' scalar -> List' scalar -> Bool #

(/=) :: List' scalar -> List' scalar -> Bool #

Ord scalar => Ord (List' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

compare :: List' scalar -> List' scalar -> Ordering #

(<) :: List' scalar -> List' scalar -> Bool #

(<=) :: List' scalar -> List' scalar -> Bool #

(>) :: List' scalar -> List' scalar -> Bool #

(>=) :: List' scalar -> List' scalar -> Bool #

max :: List' scalar -> List' scalar -> List' scalar #

min :: List' scalar -> List' scalar -> List' scalar #

Show scalar => Show (List' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

showsPrec :: Int -> List' scalar -> ShowS #

show :: List' scalar -> String #

showList :: [List' scalar] -> ShowS #

Arbitrary scalar => Arbitrary (List' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

arbitrary :: Gen (List' scalar) #

shrink :: List' scalar -> [List' scalar] #

ToJSON scalar => ToJSON (List' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

toJSON :: List' scalar -> Value #

toEncoding :: List' scalar -> Encoding #

toJSONList :: [List' scalar] -> Value #

toEncodingList :: [List' scalar] -> Encoding #

newtype String Source #

Constructors

String Text 
Instances
Eq String Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

(==) :: String -> String -> Bool #

(/=) :: String -> String -> Bool #

Ord String Source # 
Instance details

Defined in GraphQL.Internal.Value

Show String Source # 
Instance details

Defined in GraphQL.Internal.Value

Arbitrary String Source # 
Instance details

Defined in GraphQL.Internal.Value

ToJSON String Source # 
Instance details

Defined in GraphQL.Internal.Value

ToValue String Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

Names

newtype Name Source #

Constructors

Name 

Fields

Instances
Eq Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

fromString :: String -> Name #

Arbitrary Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

arbitrary :: Gen Name #

shrink :: Name -> [Name] #

ToJSON Name Source # 
Instance details

Defined in GraphQL.Internal.Name

newtype NameError Source #

An invalid name.

Constructors

NameError Text 
Instances
Eq NameError Source # 
Instance details

Defined in GraphQL.Internal.Name

Show NameError Source # 
Instance details

Defined in GraphQL.Internal.Name

GraphQLError NameError Source # 
Instance details

Defined in GraphQL.Internal.Output

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
Functor Object' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

fmap :: (a -> b) -> Object' a -> Object' b #

(<$) :: a -> Object' b -> Object' a #

Foldable Object' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

fold :: Monoid m => Object' m -> m #

foldMap :: Monoid m => (a -> m) -> Object' a -> m #

foldr :: (a -> b -> b) -> b -> Object' a -> b #

foldr' :: (a -> b -> b) -> b -> Object' a -> b #

foldl :: (b -> a -> b) -> b -> Object' a -> b #

foldl' :: (b -> a -> b) -> b -> Object' a -> b #

foldr1 :: (a -> a -> a) -> Object' a -> a #

foldl1 :: (a -> a -> a) -> Object' a -> a #

toList :: Object' a -> [a] #

null :: Object' a -> Bool #

length :: Object' a -> Int #

elem :: Eq a => a -> Object' a -> Bool #

maximum :: Ord a => Object' a -> a #

minimum :: Ord a => Object' a -> a #

sum :: Num a => Object' a -> a #

product :: Num a => Object' a -> a #

Traversable Object' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

traverse :: Applicative f => (a -> f b) -> Object' a -> f (Object' b) #

sequenceA :: Applicative f => Object' (f a) -> f (Object' a) #

mapM :: Monad m => (a -> m b) -> Object' a -> m (Object' b) #

sequence :: Monad m => Object' (m a) -> m (Object' a) #

Eq scalar => Eq (Object' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

(==) :: Object' scalar -> Object' scalar -> Bool #

(/=) :: Object' scalar -> Object' scalar -> Bool #

Ord scalar => Ord (Object' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

compare :: Object' scalar -> Object' scalar -> Ordering #

(<) :: Object' scalar -> Object' scalar -> Bool #

(<=) :: Object' scalar -> Object' scalar -> Bool #

(>) :: Object' scalar -> Object' scalar -> Bool #

(>=) :: Object' scalar -> Object' scalar -> Bool #

max :: Object' scalar -> Object' scalar -> Object' scalar #

min :: Object' scalar -> Object' scalar -> Object' scalar #

Show scalar => Show (Object' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

showsPrec :: Int -> Object' scalar -> ShowS #

show :: Object' scalar -> String #

showList :: [Object' scalar] -> ShowS #

Arbitrary scalar => Arbitrary (Object' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

arbitrary :: Gen (Object' scalar) #

shrink :: Object' scalar -> [Object' scalar] #

ToJSON scalar => ToJSON (Object' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

toJSON :: Object' scalar -> Value #

toEncoding :: Object' scalar -> Encoding #

toJSONList :: [Object' scalar] -> Value #

toEncodingList :: [Object' scalar] -> Encoding #

ToValue (Object' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

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
Functor ObjectField' Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

fmap :: (a -> b) -> ObjectField' a -> ObjectField' b #

(<$) :: a -> ObjectField' b -> ObjectField' a #

Eq scalar => Eq (ObjectField' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

(==) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

(/=) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

Ord scalar => Ord (ObjectField' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

compare :: ObjectField' scalar -> ObjectField' scalar -> Ordering #

(<) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

(<=) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

(>) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

(>=) :: ObjectField' scalar -> ObjectField' scalar -> Bool #

max :: ObjectField' scalar -> ObjectField' scalar -> ObjectField' scalar #

min :: ObjectField' scalar -> ObjectField' scalar -> ObjectField' scalar #

Show scalar => Show (ObjectField' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

showsPrec :: Int -> ObjectField' scalar -> ShowS #

show :: ObjectField' scalar -> String #

showList :: [ObjectField' scalar] -> ShowS #

Arbitrary scalar => Arbitrary (ObjectField' scalar) Source # 
Instance details

Defined in GraphQL.Internal.Value

Methods

arbitrary :: Gen (ObjectField' scalar) #

shrink :: ObjectField' scalar -> [ObjectField' scalar] #

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

unionObjects :: [Object' scalar] -> Maybe (Object' scalar) Source #

Querying

objectFields :: Object' scalar -> [ObjectField' scalar] Source #

Converting to and from Value

class ToValue a where Source #

Turn a Haskell value into a GraphQL value.

Instances
ToValue Bool Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue Double Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue Int32 Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue Text Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue List Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue String Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue Error Source # 
Instance details

Defined in GraphQL.Internal.Output

ToValue Response Source # 
Instance details

Defined in GraphQL.Internal.Output

ToValue a => ToValue [a] Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

Methods

toValue :: [a] -> Value' ConstScalar Source #

ToValue a => ToValue (Maybe a) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue a => ToValue (NonEmpty a) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue (Object' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

ToValue (Value' ConstScalar) Source # 
Instance details

Defined in GraphQL.Internal.Value.ToValue

class FromValue a where Source #

a can be converted from a GraphQL Value to a Haskell value.

The FromValue instance converts Value to the type expected by the handler function. It is the boundary between incoming data and your custom application Haskell types.

FromValue has a generic instance for converting input objects to records.

Minimal complete definition

Nothing

Methods

fromValue :: Value' ConstScalar -> Either Text a Source #

Convert an already-parsed value into a Haskell value, generally to be passed to a handler.

fromValue :: (Generic a, GenericFromValue (Rep a)) => Value' ConstScalar -> Either Text a Source #

Convert an already-parsed value into a Haskell value, generally to be passed to a handler.