Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Key = Text
- type Collection a = [(Key, a)]
- data Ref = Ref {
- refName :: Key
- refPosition :: Position
- data Position = Position {}
- type Message = Text
- anonymousRef :: Key -> Ref
- type Name = Key
- type Description = Key
- data Value
- data ScalarValue
- type Object = [(Text, Value)]
- class GQLValue a where
- gqlNull :: a
- gqlScalar :: ScalarValue -> a
- gqlBoolean :: Bool -> a
- gqlString :: Text -> a
- gqlList :: [a] -> a
- gqlObject :: [(Text, a)] -> a
- replaceValue :: Value -> Value
- decodeScientific :: Scientific -> ScalarValue
- convertToJSONName :: Text -> Text
- convertToHaskellName :: Text -> Text
- data Argument = Argument {}
- type Arguments = Collection Argument
- type SelectionSet = Collection ValidSelection
- data SelectionRec
- = SelectionSet SelectionSet
- | UnionSelection UnionSelection
- | SelectionField
- data ValueOrigin
- type ValidSelection = Selection Arguments SelectionRec
- data Selection args rec = Selection {
- selectionArguments :: args
- selectionPosition :: Position
- selectionAlias :: Maybe Key
- selectionRec :: rec
- type RawSelection' a = Selection RawArguments a
- type FragmentLib = [(Key, Fragment)]
- type RawArguments = Collection RawArgument
- type RawSelectionSet = Collection RawSelection
- data Fragment = Fragment {}
- data RawArgument
- data RawSelection
- data Operation args sel = Operation {
- operationName :: Maybe Key
- operationType :: OperationType
- operationArgs :: args
- operationSelection :: sel
- operationPosition :: Position
- data Variable a = Variable {}
- type ValidOperation = Operation Arguments SelectionSet
- type RawOperation = Operation VariableDefinitions RawSelectionSet
- type VariableDefinitions = Collection (Variable DefaultValue)
- type ValidVariables = Collection (Variable Value)
- type DefaultValue = Maybe Value
- getOperationName :: Maybe Key -> Key
- getOperationDataType :: Operation a b -> DataTypeLib -> Validation DataObject
- type DataScalar = DataTyCon DataValidator
- type DataEnum = DataTyCon [DataEnumValue]
- type DataObject = DataTyCon [(Key, DataField)]
- type DataArgument = DataField
- type DataUnion = DataTyCon [Key]
- type DataArguments = [(Key, DataArgument)]
- data DataField = DataField {}
- data DataTyCon a = DataTyCon {
- typeName :: Key
- typeFingerprint :: DataFingerprint
- typeMeta :: Maybe Meta
- typeData :: a
- data DataType
- data DataTypeLib = DataTypeLib {
- types :: HashMap Key DataType
- query :: (Key, DataObject)
- mutation :: Maybe (Key, DataObject)
- subscription :: Maybe (Key, DataObject)
- data DataTypeWrapper
- newtype DataValidator = DataValidator {
- validateValue :: Value -> Either Key Value
- data DataTypeKind
- data DataFingerprint
- data RawDataType
- data ResolverKind
- data TypeWrapper
- data TypeAlias = TypeAlias {
- aliasTyCon :: Key
- aliasArgs :: Maybe Key
- aliasWrappers :: [TypeWrapper]
- data ArgsType = ArgsType {}
- data DataEnumValue = DataEnumValue {}
- isTypeDefined :: Key -> DataTypeLib -> Maybe DataFingerprint
- initTypeLib :: (Key, DataObject) -> DataTypeLib
- defineType :: (Key, DataType) -> DataTypeLib -> DataTypeLib
- isFieldNullable :: DataField -> Bool
- allDataTypes :: DataTypeLib -> [(Key, DataType)]
- lookupDataType :: Key -> DataTypeLib -> Maybe DataType
- kindOf :: DataType -> DataTypeKind
- toNullableField :: DataField -> DataField
- toListField :: DataField -> DataField
- isObject :: DataTypeKind -> Bool
- isInput :: DataTypeKind -> Bool
- toHSWrappers :: [DataTypeWrapper] -> [TypeWrapper]
- isNullable :: [TypeWrapper] -> Bool
- toGQLWrapper :: [TypeWrapper] -> [DataTypeWrapper]
- isWeaker :: [TypeWrapper] -> [TypeWrapper] -> Bool
- isSubscription :: DataTypeKind -> Bool
- isOutputObject :: DataTypeKind -> Bool
- sysTypes :: [Key]
- isDefaultTypeName :: Key -> Bool
- isSchemaTypeName :: Key -> Bool
- isPrimitiveTypeName :: Key -> Bool
- data OperationType
- type QUERY = Query
- type MUTATION = Mutation
- type SUBSCRIPTION = Subscription
- isEntNode :: DataType -> Bool
- lookupInputType :: Failure e m => Key -> DataTypeLib -> e -> m DataType
- coerceDataObject :: Failure error m => error -> DataType -> m DataObject
- getDataType :: Failure error m => Key -> DataTypeLib -> error -> m DataType
- lookupDataObject :: (Monad m, Failure e m) => e -> Key -> DataTypeLib -> m DataObject
- lookupDataUnion :: (Monad m, Failure e m) => e -> Key -> DataTypeLib -> m DataUnion
- lookupType :: Failure e m => e -> [(Key, a)] -> Key -> m a
- lookupField :: Failure error m => Key -> [(Key, field)] -> error -> m field
- lookupUnionTypes :: (Monad m, Failure GQLErrors m) => Position -> Key -> DataTypeLib -> DataField -> m [DataObject]
- lookupSelectionField :: Failure GQLErrors Validation => Position -> Key -> DataObject -> Validation DataField
- lookupFieldAsSelectionSet :: (Monad m, Failure GQLErrors m) => Position -> Key -> DataTypeLib -> DataField -> m DataObject
- createField :: DataArguments -> Key -> ([TypeWrapper], Key) -> DataField
- createArgument :: Key -> ([TypeWrapper], Key) -> (Key, DataField)
- createDataTypeLib :: [(Key, DataType)] -> Validation DataTypeLib
- createEnumType :: Key -> [Key] -> (Key, DataType)
- createScalarType :: Key -> (Key, DataType)
- createType :: Key -> a -> DataTyCon a
- createUnionType :: Key -> [Key] -> (Key, DataType)
- createAlias :: Key -> TypeAlias
- createInputUnionFields :: Key -> [Key] -> [(Key, DataField)]
- fieldVisibility :: (Key, DataField) -> Bool
- data Meta = Meta {}
- data Directive = Directive {
- directiveName :: Name
- directiveArgs :: [(Name, Value)]
- createEnumValue :: Key -> DataEnumValue
- fromDataType :: (DataTyCon () -> v) -> DataType -> v
- insertType :: (Key, DataType) -> TypeUpdater
- type TypeUpdater = LibUpdater DataTypeLib
- lookupDeprecated :: Meta -> Maybe Directive
- lookupDeprecatedReason :: Directive -> Maybe Key
- data TypeD = TypeD {}
- data ConsD = ConsD {}
- data ClientQuery = ClientQuery {
- queryText :: String
- queryTypes :: [ClientType]
- queryArgsType :: Maybe TypeD
- data GQLTypeD = GQLTypeD {
- typeD :: TypeD
- typeKindD :: DataTypeKind
- typeArgD :: [TypeD]
- typeOriginal :: (Name, DataType)
- data ClientType = ClientType {}
- data GQLQuery = GQLQuery {
- fragments :: FragmentLib
- operation :: RawOperation
- inputVariables :: [(Key, Value)]
- type Variables = Map Key Value
Documentation
type Collection a = [(Key, a)] Source #
Ref | |
|
Instances
Show Position Source # | |
Generic Position Source # | |
Lift Position Source # | |
ToJSON Position Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Base | |
FromJSON Position Source # | |
type Rep Position Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Base type Rep Position = D1 (MetaData "Position" "Data.Morpheus.Types.Internal.AST.Base" "morpheus-graphql-0.7.0-1athT4IXRfbLIB7DZAaUGv" False) (C1 (MetaCons "Position" PrefixI True) (S1 (MetaSel (Just "line") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "column") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
anonymousRef :: Key -> Ref Source #
type Description = Key Source #
Instances
data ScalarValue Source #
Primitive Values for GQLScalar: ScalarValue
, ScalarValue
, ScalarValue
, Boolean
.
for performance reason type Text
represents GraphQl ScalarValue
value
Instances
class GQLValue a where Source #
gqlScalar :: ScalarValue -> a Source #
gqlBoolean :: Bool -> a Source #
replaceValue :: Value -> Value Source #
convertToJSONName :: Text -> Text Source #
convertToHaskellName :: Text -> Text Source #
type Arguments = Collection Argument Source #
type SelectionSet = Collection ValidSelection Source #
data SelectionRec Source #
SelectionSet SelectionSet | |
UnionSelection UnionSelection | |
SelectionField |
Instances
Show SelectionRec Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection showsPrec :: Int -> SelectionRec -> ShowS # show :: SelectionRec -> String # showList :: [SelectionRec] -> ShowS # |
data ValueOrigin Source #
Instances
Show ValueOrigin Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection showsPrec :: Int -> ValueOrigin -> ShowS # show :: ValueOrigin -> String # showList :: [ValueOrigin] -> ShowS # | |
Lift ValueOrigin Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection lift :: ValueOrigin -> Q Exp # |
data Selection args rec Source #
Selection | |
|
type RawSelection' a = Selection RawArguments a Source #
type FragmentLib = [(Key, Fragment)] Source #
type RawArguments = Collection RawArgument Source #
type RawSelectionSet = Collection RawSelection Source #
data RawArgument Source #
Instances
Show RawArgument Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection showsPrec :: Int -> RawArgument -> ShowS # show :: RawArgument -> String # showList :: [RawArgument] -> ShowS # | |
Lift RawArgument Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection lift :: RawArgument -> Q Exp # |
data RawSelection Source #
RawSelectionSet (RawSelection' RawSelectionSet) | |
RawSelectionField (RawSelection' ()) | |
InlineFragment Fragment | |
Spread Ref |
Instances
Show RawSelection Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection showsPrec :: Int -> RawSelection -> ShowS # show :: RawSelection -> String # showList :: [RawSelection] -> ShowS # | |
Lift RawSelection Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Selection lift :: RawSelection -> Q Exp # |
data Operation args sel Source #
Operation | |
|
Variable | |
|
type VariableDefinitions = Collection (Variable DefaultValue) Source #
type ValidVariables = Collection (Variable Value) Source #
type DefaultValue = Maybe Value Source #
getOperationDataType :: Operation a b -> DataTypeLib -> Validation DataObject Source #
type DataScalar = DataTyCon DataValidator Source #
type DataEnum = DataTyCon [DataEnumValue] Source #
type DataArgument = DataField Source #
type DataArguments = [(Key, DataArgument)] Source #
DataTyCon | |
|
data DataTypeLib Source #
DataTypeLib | |
|
Instances
Show DataTypeLib Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataTypeLib -> ShowS # show :: DataTypeLib -> String # showList :: [DataTypeLib] -> ShowS # |
data DataTypeWrapper Source #
Instances
Show DataTypeWrapper Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataTypeWrapper -> ShowS # show :: DataTypeWrapper -> String # showList :: [DataTypeWrapper] -> ShowS # | |
Lift DataTypeWrapper Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: DataTypeWrapper -> Q Exp # |
newtype DataValidator Source #
Instances
Show DataValidator Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataValidator -> ShowS # show :: DataValidator -> String # showList :: [DataValidator] -> ShowS # |
data DataTypeKind Source #
KindScalar | |
KindObject (Maybe OperationType) | |
KindUnion | |
KindEnum | |
KindInputObject | |
KindList | |
KindNonNull | |
KindInputUnion |
Instances
Eq DataTypeKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data (==) :: DataTypeKind -> DataTypeKind -> Bool # (/=) :: DataTypeKind -> DataTypeKind -> Bool # | |
Show DataTypeKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataTypeKind -> ShowS # show :: DataTypeKind -> String # showList :: [DataTypeKind] -> ShowS # | |
Lift DataTypeKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: DataTypeKind -> Q Exp # |
data DataFingerprint Source #
Instances
Eq DataFingerprint Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data (==) :: DataFingerprint -> DataFingerprint -> Bool # (/=) :: DataFingerprint -> DataFingerprint -> Bool # | |
Ord DataFingerprint Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data compare :: DataFingerprint -> DataFingerprint -> Ordering # (<) :: DataFingerprint -> DataFingerprint -> Bool # (<=) :: DataFingerprint -> DataFingerprint -> Bool # (>) :: DataFingerprint -> DataFingerprint -> Bool # (>=) :: DataFingerprint -> DataFingerprint -> Bool # max :: DataFingerprint -> DataFingerprint -> DataFingerprint # min :: DataFingerprint -> DataFingerprint -> DataFingerprint # | |
Show DataFingerprint Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataFingerprint -> ShowS # show :: DataFingerprint -> String # showList :: [DataFingerprint] -> ShowS # | |
Lift DataFingerprint Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: DataFingerprint -> Q Exp # |
data RawDataType Source #
Instances
Show RawDataType Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> RawDataType -> ShowS # show :: RawDataType -> String # showList :: [RawDataType] -> ShowS # |
data ResolverKind Source #
Instances
Eq ResolverKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data (==) :: ResolverKind -> ResolverKind -> Bool # (/=) :: ResolverKind -> ResolverKind -> Bool # | |
Show ResolverKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> ResolverKind -> ShowS # show :: ResolverKind -> String # showList :: [ResolverKind] -> ShowS # | |
Lift ResolverKind Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: ResolverKind -> Q Exp # |
data TypeWrapper Source #
Instances
Show TypeWrapper Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> TypeWrapper -> ShowS # show :: TypeWrapper -> String # showList :: [TypeWrapper] -> ShowS # | |
Lift TypeWrapper Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: TypeWrapper -> Q Exp # |
TypeAlias | |
|
data DataEnumValue Source #
Instances
Show DataEnumValue Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> DataEnumValue -> ShowS # show :: DataEnumValue -> String # showList :: [DataEnumValue] -> ShowS # | |
Lift DataEnumValue Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: DataEnumValue -> Q Exp # |
isTypeDefined :: Key -> DataTypeLib -> Maybe DataFingerprint Source #
initTypeLib :: (Key, DataObject) -> DataTypeLib Source #
defineType :: (Key, DataType) -> DataTypeLib -> DataTypeLib Source #
isFieldNullable :: DataField -> Bool Source #
allDataTypes :: DataTypeLib -> [(Key, DataType)] Source #
lookupDataType :: Key -> DataTypeLib -> Maybe DataType Source #
kindOf :: DataType -> DataTypeKind Source #
toNullableField :: DataField -> DataField Source #
toListField :: DataField -> DataField Source #
isObject :: DataTypeKind -> Bool Source #
isInput :: DataTypeKind -> Bool Source #
toHSWrappers :: [DataTypeWrapper] -> [TypeWrapper] Source #
isNullable :: [TypeWrapper] -> Bool Source #
toGQLWrapper :: [TypeWrapper] -> [DataTypeWrapper] Source #
isWeaker :: [TypeWrapper] -> [TypeWrapper] -> Bool Source #
isSubscription :: DataTypeKind -> Bool Source #
isOutputObject :: DataTypeKind -> Bool Source #
isDefaultTypeName :: Key -> Bool Source #
isSchemaTypeName :: Key -> Bool Source #
isPrimitiveTypeName :: Key -> Bool Source #
data OperationType Source #
Instances
Eq OperationType Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data (==) :: OperationType -> OperationType -> Bool # (/=) :: OperationType -> OperationType -> Bool # | |
Show OperationType Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> OperationType -> ShowS # show :: OperationType -> String # showList :: [OperationType] -> ShowS # | |
Lift OperationType Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data lift :: OperationType -> Q Exp # |
type SUBSCRIPTION = Subscription Source #
lookupInputType :: Failure e m => Key -> DataTypeLib -> e -> m DataType Source #
coerceDataObject :: Failure error m => error -> DataType -> m DataObject Source #
getDataType :: Failure error m => Key -> DataTypeLib -> error -> m DataType Source #
lookupDataObject :: (Monad m, Failure e m) => e -> Key -> DataTypeLib -> m DataObject Source #
lookupDataUnion :: (Monad m, Failure e m) => e -> Key -> DataTypeLib -> m DataUnion Source #
lookupType :: Failure e m => e -> [(Key, a)] -> Key -> m a Source #
lookupField :: Failure error m => Key -> [(Key, field)] -> error -> m field Source #
lookupUnionTypes :: (Monad m, Failure GQLErrors m) => Position -> Key -> DataTypeLib -> DataField -> m [DataObject] Source #
lookupSelectionField :: Failure GQLErrors Validation => Position -> Key -> DataObject -> Validation DataField Source #
lookupFieldAsSelectionSet :: (Monad m, Failure GQLErrors m) => Position -> Key -> DataTypeLib -> DataField -> m DataObject Source #
createField :: DataArguments -> Key -> ([TypeWrapper], Key) -> DataField Source #
createArgument :: Key -> ([TypeWrapper], Key) -> (Key, DataField) Source #
createDataTypeLib :: [(Key, DataType)] -> Validation DataTypeLib Source #
createType :: Key -> a -> DataTyCon a Source #
createAlias :: Key -> TypeAlias Source #
Directive | |
|
createEnumValue :: Key -> DataEnumValue Source #
fromDataType :: (DataTyCon () -> v) -> DataType -> v Source #
insertType :: (Key, DataType) -> TypeUpdater Source #
type TypeUpdater = LibUpdater DataTypeLib Source #
data ClientQuery Source #
ClientQuery | |
|
Instances
Show ClientQuery Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> ClientQuery -> ShowS # show :: ClientQuery -> String # showList :: [ClientQuery] -> ShowS # |
GQLTypeD | |
|
data ClientType Source #
Instances
Show ClientType Source # | |
Defined in Data.Morpheus.Types.Internal.AST.Data showsPrec :: Int -> ClientType -> ShowS # show :: ClientType -> String # showList :: [ClientType] -> ShowS # |
GQLQuery | |
|