diff --git a/source/AirGQL/GraphQL.hs b/source/AirGQL/GraphQL.hs index 2d7abb7..39bfc30 100644 --- a/source/AirGQL/GraphQL.hs +++ b/source/AirGQL/GraphQL.hs @@ -40,6 +40,7 @@ import Protolude ( (<=), (>), (>=), + (||), ) import Protolude qualified as P @@ -213,33 +214,36 @@ getColNamesQuoted columnEntries = opAndValToSql :: HashMap.HashMap Text Value -> [Text] opAndValToSql operatorAndValue = case HashMap.toList operatorAndValue of - [("eq", value)] -> - pure $ - if value == Null - then " IS NULL" - else " == " <> gqlValueToSQLText value - [("neq", value)] -> - if value == Null - then pure " IS NOT NULL" - else - [ " != " <> gqlValueToSQLText value - , " IS NULL" - ] - [("in", List values)] -> - let listValues = values <&> gqlValueToSQLText & intercalate "," - in [" IN (" <> listValues <> ")"] - [("nin", List values)] -> - let listValues = values <&> gqlValueToSQLText & intercalate "," - in [" NOT IN (" <> listValues <> ")"] - <> if P.elem Null values - then [] - else [" IS NULL"] - [("gt", value)] -> [" > " <> gqlValueToSQLText value] - [("gte", value)] -> [" >= " <> gqlValueToSQLText value] - [("lt", value)] -> [" < " <> gqlValueToSQLText value] - [("lte", value)] -> [" <= " <> gqlValueToSQLText value] - [("like", value)] -> [" like " <> gqlValueToSQLText value] - [("ilike", value)] -> [" like " <> gqlValueToSQLText value] + [(op, value)] + | op == "eq" || op == "_eq" -> + pure $ + if value == Null + then " IS NULL" + else " == " <> gqlValueToSQLText value + | op == "neq" || op == "_neq" -> + if value == Null + then pure " IS NOT NULL" + else + [ " != " <> gqlValueToSQLText value + , " IS NULL" + ] + | op == "in" || op == "_in" + , List values <- value -> + let listValues = values <&> gqlValueToSQLText & intercalate "," + in [" IN (" <> listValues <> ")"] + | op == "nin" || op == "_nin" + , List values <- value -> + let listValues = values <&> gqlValueToSQLText & intercalate "," + in [" NOT IN (" <> listValues <> ")"] + <> if P.elem Null values + then [] + else [" IS NULL"] + | op == "gt" || op == "_gt" -> [" > " <> gqlValueToSQLText value] + | op == "gte" || op == "_gte" -> [" >= " <> gqlValueToSQLText value] + | op == "lt" || op == "_lt" -> [" < " <> gqlValueToSQLText value] + | op == "lte" || op == "_lte" -> [" <= " <> gqlValueToSQLText value] + | op == "like" || op == "_like" -> [" like " <> gqlValueToSQLText value] + | op == "ilike" || op == "_ilike" -> [" like " <> gqlValueToSQLText value] filter -> do throw $ userError $ @@ -451,16 +455,21 @@ rowsToGraphQL dbId table updatedRows = & List +-- Attempts to find and decode an argument, given its current name, and a list +-- of deprecated older names. tryGetArg :: forall m a . (FromGraphQL a) => (MonadIO m) => Text + -> [Text] -> HashMap Text Value -> m (Maybe a) -tryGetArg name args = do +tryGetArg name alts args = do case HashMap.lookup name args of - Nothing -> pure Nothing + Nothing -> case alts of + alt : others -> tryGetArg alt others args + [] -> pure Nothing Just value -> case fromGraphQL value of Just decoded -> pure $ Just decoded @@ -470,15 +479,17 @@ tryGetArg name args = do "Argument " <> T.unpack name <> " has invalid format" +-- Similar to `tryGetArg`, but will error out on failure. getArg :: forall m a . (FromGraphQL a) => (MonadIO m) => Text + -> [Text] -> HashMap Text Value -> m a -getArg name args = do - result <- tryGetArg name args +getArg name alts args = do + result <- tryGetArg name alts args case result of Just value -> pure value Nothing -> @@ -487,16 +498,18 @@ getArg name args = do "Argument " <> T.unpack name <> " not found" +-- Similar to `tryGetArg`, but will return a custom value on failure. getArgWithDefault :: forall m a . (FromGraphQL a) => (MonadIO m) => Text + -> [Text] -> HashMap Text Value -> a -> m a -getArgWithDefault name args def = - tryGetArg name args <&> P.fromMaybe def +getArgWithDefault name alts args def = + tryGetArg name alts args <&> P.fromMaybe def executeUpdateMutation @@ -608,13 +621,8 @@ queryType connection accessMode dbId tables = do rows :: [[SQLData]] <- case context.arguments of Arguments args -> do - filterElements <- case args & HashMap.lookup "filter" of - Nothing -> pure [] - Just colToFilter -> case colToFilter of - Object filterObj -> case HashMap.toList filterObj of - [] -> P.throwIO $ userError "Error: Filter must not be empty" - filterElements -> pure filterElements - _ -> pure [] + filterElements :: HashMap Text Value <- + getArgWithDefault "where" ["filter"] args HashMap.empty orderElements :: [(Name, Value)] <- case args & HashMap.lookup "order_by" of @@ -678,7 +686,7 @@ queryType connection accessMode dbId tables = do [ "SELECT COUNT() FROM" , quoteKeyword table.name , "\n" - , getWhereClause filterElements + , getWhereClause $ HashMap.toList filterElements ] -- Will be equal `Just numRows` when the number of @@ -720,7 +728,7 @@ queryType connection accessMode dbId tables = do connection table.name table.columns - filterElements + (HashMap.toList filterElements) orderElements paginationMb @@ -849,7 +857,7 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do -- [ { name: "John", email: "john@example.com" } -- , { name: "Eve", email: "eve@example.com" } -- ] - values :: [HashMap Text Value] <- getArg "objects" argMap + values :: [HashMap Text Value] <- getArg "objects" [] argMap let -- All colums that are contained in the entries containedColumns :: [Text] @@ -866,12 +874,12 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do <&> (\name -> ":" <> doubleXEncodeGql name) onConflictArg :: [HashMap Text Value] <- - getArgWithDefault "on_conflict" argMap [] + getArgWithDefault "on_conflict" [] argMap [] onConflictClauses <- P.for onConflictArg $ \fields -> do let getColumnList fieldName = - getArgWithDefault fieldName fields [] + getArgWithDefault fieldName [] fields [] <&> P.mapMaybe ( \case Enum columnName -> Just columnName @@ -895,7 +903,7 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do <> " = :" <> doubleXEncodeGql column - filterElements <- getArgWithDefault "where" fields mempty + filterElements <- getArgWithDefault "where" ["filter"] fields mempty pure $ "ON CONFLICT (" @@ -983,8 +991,8 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do context <- ask let Arguments args = context.arguments liftIO $ do - filterObj <- getArg "filter" args - pairsToSet <- getArg "set" args + filterObj <- getArg "where" ["filter"] args + pairsToSet <- getArg "_set" ["set"] args (numOfChanges, updatedRows) <- case HashMap.toList filterObj of [] -> P.throwIO $ userError "Error: Filter must not be empty" filterElements -> @@ -1002,11 +1010,17 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do let Arguments args = context.arguments let filterElements = args - & HashMap.delete "set" + & HashMap.delete (encodeOutsidePKNames table "_set") + & HashMap.delete (encodeOutsidePKNames table "set") & getByPKFilterElements liftIO $ do - pairsToSet <- getArg (encodeOutsidePKNames table "set") args + pairsToSet <- + getArg + (encodeOutsidePKNames table "_set") + [encodeOutsidePKNames table "set"] + args + (numOfChanges, updatedRows) <- executeUpdateMutation connection @@ -1023,7 +1037,7 @@ mutationType connection maxRowsPerTable accessMode dbId tables = do let Arguments args = context.arguments liftIO $ do - filterElements <- getArg "filter" args + filterElements <- getArg "where" ["filter"] args let sqlQuery = Query $ P.unlines diff --git a/source/AirGQL/Introspection.hs b/source/AirGQL/Introspection.hs index b87ee63..b093a2b 100644 --- a/source/AirGQL/Introspection.hs +++ b/source/AirGQL/Introspection.hs @@ -114,22 +114,30 @@ filterType table = do let colName = columnEntry.column_name_gql let typeName = columnTypeName columnEntry let type_ = columnType columnEntry - Type.inputValue colName $ - Type.withDescription ("Compare to a(n) " <> typeName) $ - Type.inputObject - (typeName <> "Comparison") - [ Type.inputValue "eq" type_ - , Type.inputValue "neq" type_ - , Type.inputValue "gt" type_ - , Type.inputValue "gte" type_ - , Type.inputValue "lt" type_ - , Type.inputValue "lte" type_ - , Type.inputValue "like" type_ - , Type.inputValue "ilike" type_ - , Type.inputValue "in" $ Type.list type_ - , Type.inputValue "nin" $ Type.list type_ + + let comparisonField name ty = + [ Type.deprecatedInputValue "Unify naming with Hasura" $ + Type.inputValue name ty + , Type.inputValue ("_" <> name) ty ] + Type.inputValue colName + $ Type.withDescription ("Compare to a(n) " <> typeName) + $ Type.inputObject + (typeName <> "Comparison") + $ P.fold + [ comparisonField "eq" type_ + , comparisonField "neq" type_ + , comparisonField "gt" type_ + , comparisonField "gte" type_ + , comparisonField "lt" type_ + , comparisonField "lte" type_ + , comparisonField "like" type_ + , comparisonField "ilike" type_ + , comparisonField "in" $ Type.list type_ + , comparisonField "nin" $ Type.list type_ + ] + Type.inputObject (doubleXEncodeGql table.name <> "_filter") fieldsWithComparisonExp @@ -175,9 +183,12 @@ tableQueryField table = (Type.nonNull $ Type.list $ Type.nonNull $ tableRowType table) & Type.fieldWithDescription ("Rows from the table \"" <> table.name <> "\"") & Type.withArguments - [ Type.inputValue "filter" (filterType table) + ( Type.inputValue "filter" (filterType table) & Type.inputValueWithDescription "Filter to select specific rows" - , Type.inputValue "order_by" (Type.list orderType) + & Type.renameInputValue "where" "Unify naming with Hasura" + ) + & Type.withArguments + [ Type.inputValue "order_by" (Type.list orderType) & Type.inputValueWithDescription "Columns used to sort the data" , Type.inputValue "limit" Type.typeInt & Type.inputValueWithDescription "Limit the number of returned rows" @@ -359,15 +370,19 @@ tableUpdateField accessMode table = do & Type.fieldWithDescription ("Update rows in table \"" <> table.name <> "\"") & Type.withArguments - [ Type.inputValue + ( Type.inputValue "set" - (Type.nonNull $ tableSetInput table) + (tableSetInput table) & Type.inputValueWithDescription "Fields to be updated" - , Type.inputValue + & Type.renameInputValue "_set" "Unify naming with Hasura" + ) + & Type.withArguments + ( Type.inputValue "filter" - (Type.nonNull $ filterType table) + (filterType table) & Type.inputValueWithDescription "Filter to select rows to be updated" - ] + & Type.renameInputValue "where" "Unify naming with Hasura" + ) tableUpdateFieldByPk @@ -378,14 +393,6 @@ tableUpdateFieldByPk tableUpdateFieldByPk accessMode tables table = do pkArguments <- tablePKArguments table - let arguments = - [ Type.inputValue - (encodeOutsidePKNames table "set") - (Type.nonNull $ tableSetInput table) - & Type.inputValueWithDescription "Fields to be updated" - ] - <> pkArguments - pure $ Type.field ( "update_" @@ -398,7 +405,16 @@ tableUpdateFieldByPk accessMode tables table = do (Type.nonNull $ mutationByPkResponseType accessMode table) & Type.fieldWithDescription ("Update row in table \"" <> table.name <> "\" by PK") - & Type.withArguments arguments + & Type.withArguments pkArguments + & Type.withArguments + ( Type.inputValue + (encodeOutsidePKNames table "set") + (tableSetInput table) + & Type.inputValueWithDescription "Fields to be updated" + & Type.renameInputValue + (encodeOutsidePKNames table "_set") + "Unify naming with Hasura" + ) tableDeleteField :: AccessMode -> TableEntry -> Type.Field @@ -409,11 +425,12 @@ tableDeleteField accessMode table = do & Type.fieldWithDescription ("Delete rows in table \"" <> table.name <> "\"") & Type.withArguments - [ Type.inputValue + ( Type.inputValue "filter" - (Type.nonNull $ filterType table) + (filterType table) & Type.inputValueWithDescription "Filter to select rows to be deleted" - ] + & Type.renameInputValue "where" "Unify naming with Hasura" + ) tableDeleteFieldByPK diff --git a/source/AirGQL/Introspection/Resolver.hs b/source/AirGQL/Introspection/Resolver.hs index 95aa6bf..f988b0c 100644 --- a/source/AirGQL/Introspection/Resolver.hs +++ b/source/AirGQL/Introspection/Resolver.hs @@ -30,6 +30,7 @@ import Control.Exception qualified as Exception import Data.HashMap.Strict qualified as HashMap import Data.Text qualified as T import GHC.IO.Exception (userError) +import Language.GraphQL.Class (ToGraphQL (toGraphQL)) import Language.GraphQL.Error (ResolverException (ResolverException)) import Language.GraphQL.Type qualified as Type import Language.GraphQL.Type.In qualified as In @@ -101,7 +102,7 @@ makeType = if depth >= 30 then makeConstField - (IType.field field.name IType.typeString) + (IType.field field.name $ IType.nonNull IType.typeString) (Type.String "Maximum depth exceeded") else makeChildField (depth + 1) field pure (field.name, resolver) @@ -111,21 +112,20 @@ makeType = (IType.field "__typename" $ IType.nonNull IType.typeString) (Type.String name) - pure - $ Out.NamedObjectType - $ Type.ObjectType - name - ty.description - [] - $ HashMap.fromList - $ ("__typename", typenameResolver) : resolvers + pure $ + Out.NamedObjectType $ + Type.ObjectType name ty.description [] $ + HashMap.fromList $ + ("__typename", typenameResolver) : resolvers _ -> do - Left $ "invalid type in out position: " <> show ty.kind + Left $ "invalid type in out position: " <> show (toGraphQL ty) - -- Creates a field which looks up it's value in the object returned by the + -- Creates a field which looks up its value in the object returned by the -- parent resolver. makeChildField :: Int -> IType.Field -> Result (Out.Resolver IO) makeChildField depth field = do + -- These lines are the same as `makeField`, except calling + -- `makeTypeWithDepthMemo` instead of `makeType` args <- P.for field.args $ \arg -> do ty <- makeInType arg.type_ pure (arg.name, In.Argument arg.description ty arg.defaultValue) @@ -144,7 +144,7 @@ makeType = <> "' not found " else pure Type.Null - case context.values of + result <- case context.values of Type.Object obj -> do let errorValue = HashMap.lookup ("__error_" <> field.name) obj P.for_ errorValue $ \case @@ -155,6 +155,8 @@ makeType = Just value -> pure value Nothing -> defaultValue _ -> defaultValue + + field.customResolver result in makeTypeWithDepth 0 @@ -219,4 +221,4 @@ makeInType ty = do ty.description $ HashMap.fromList gqlFields _ -> do - Left $ "invalid type in input position: " <> show ty.kind + Left $ "invalid type in input position: " <> show (toGraphQL ty) diff --git a/source/AirGQL/Introspection/Types.hs b/source/AirGQL/Introspection/Types.hs index 56b757f..7910d37 100644 --- a/source/AirGQL/Introspection/Types.hs +++ b/source/AirGQL/Introspection/Types.hs @@ -16,9 +16,12 @@ module AirGQL.Introspection.Types ( enumValueWithDescription, field, fieldWithDescription, + deprecatedField, inputObject, inputValue, inputValueWithDescription, + deprecatedInputValue, + renameInputValue, list, nonNull, object, @@ -40,13 +43,15 @@ module AirGQL.Introspection.Types ( import Protolude ( Bool (False, True), Generic, + IO, Maybe (Just, Nothing), + MonadReader (ask), MonadState (get, put), Monoid (mempty), - Show, State, Text, execState, + filter, for_, not, pure, @@ -54,8 +59,10 @@ import Protolude ( when, ($), (&), + (/=), (<$>), (<>), + (==), ) import Data.HashMap.Strict (HashMap) @@ -71,7 +78,7 @@ data Schema = Schema , mutationType :: Maybe IntrospectionType , directives :: [Directive] } - deriving (Show, Generic) + deriving (Generic) instance ToGraphQL Schema where @@ -98,14 +105,14 @@ data TypeKind | InputObject Name [InputValue] | List IntrospectionType | NonNull IntrospectionType - deriving (Show, Generic) + deriving (Generic) data IntrospectionType = IType { kind :: TypeKind , description :: Maybe Text } - deriving (Show, Generic) + deriving (Generic) instance ToGraphQL IntrospectionType where @@ -214,8 +221,11 @@ data Field = Field , type_ :: IntrospectionType , isDeprecated :: Bool , deprecationReason :: Maybe Text + , -- Allows injecting custom logic into the resulting resolver. The function + -- is given the value of the field in the parent object. + customResolver :: Value.Value -> Value.Resolve IO } - deriving (Show, Generic) + deriving (Generic) instance ToGraphQL Field where @@ -231,14 +241,6 @@ instance ToGraphQL Field where ] -fieldWithDescription :: Text -> Field -> Field -fieldWithDescription newDesc (Field{..}) = - Field - { description = Just newDesc - , .. - } - - field :: Text -> IntrospectionType -> Field field fieldName fieldType = Field @@ -248,6 +250,24 @@ field fieldName fieldType = , type_ = fieldType , isDeprecated = False , deprecationReason = Nothing + , customResolver = pure + } + + +fieldWithDescription :: Text -> Field -> Field +fieldWithDescription newDesc (Field{..}) = + Field + { description = Just newDesc + , .. + } + + +deprecatedField :: Text -> Field -> Field +deprecatedField reason (Field{..}) = + Field + { isDeprecated = True + , deprecationReason = Just reason + , .. } @@ -260,8 +280,10 @@ data InputValue = InputValue , description :: Maybe Text , type_ :: IntrospectionType , defaultValue :: Maybe Value.Value + , isDeprecated :: Bool + , deprecationReason :: Maybe Text } - deriving (Show, Generic) + deriving (Generic) instance ToGraphQL InputValue where @@ -278,6 +300,8 @@ instance ToGraphQL InputValue where Nothing -> Value.Null Just s -> Value.String $ show s ) + , ("isDeprecated", toGraphQL value.isDeprecated) + , ("deprecationReason", toGraphQL value.deprecationReason) ] @@ -288,6 +312,8 @@ inputValue fieldName fieldType = , description = Nothing , type_ = fieldType , defaultValue = Nothing + , isDeprecated = False + , deprecationReason = Nothing } @@ -307,13 +333,37 @@ withDefaultValue newValue (InputValue{..}) = } +deprecatedInputValue :: Text -> InputValue -> InputValue +deprecatedInputValue reason (InputValue{..}) = + InputValue + { isDeprecated = True + , deprecationReason = Just reason + , .. + } + + +-- Rename an input value, deprecating the old version. +renameInputValue :: Text -> Text -> InputValue -> [InputValue] +renameInputValue to reason (InputValue{..}) = + [ InputValue + { name = to + , .. + } + , InputValue + { isDeprecated = True + , deprecationReason = Just reason + , .. + } + ] + + data EnumValue = EnumValue { name :: Text , description :: Maybe Text , isDeprecated :: Bool , deprecationReason :: Maybe Text } - deriving (Show, Generic) + deriving (Generic) instance ToGraphQL EnumValue where @@ -358,7 +408,7 @@ data Directive = Directive , args :: [InputValue] , isRepeatable :: Bool } - deriving (Generic, Show) + deriving (Generic) instance ToGraphQL Directive where @@ -486,7 +536,8 @@ typeField = "__Field" [ field "name" $ nonNull typeString , field "description" typeString - , field "args" $ nonNull $ list $ nonNull typeInputValue + , field "args" (nonNull $ list $ nonNull typeInputValue) + & typeWithDeprecatedFilter , field "type" $ nonNull typeIntrospectionType , field "isDeprecated" $ nonNull typeBool , field "deprecationReason" typeString @@ -507,6 +558,8 @@ typeInputValue = & fieldWithDescription "A GraphQL-formatted string representing \ \the default value for this input value." + , field "isDeprecated" $ nonNull typeBool + , field "deprecationReason" typeString ] & withDescription "Arguments provided to Fields or Directives and the input \ @@ -574,16 +627,11 @@ typeIntrospectionType = , field "interfaces" $ list $ nonNull typeIntrospectionType , field "possibleTypes" $ list $ nonNull typeIntrospectionType , field "fields" (list $ nonNull typeField) - & withArguments - [ inputValue "includeDeprecated" typeBool - & withDefaultValue (toGraphQL False) - ] + & typeWithDeprecatedFilter , field "enumValues" (list $ nonNull typeEnumValue) - & withArguments - [ inputValue "includeDeprecated" typeBool - & withDefaultValue (toGraphQL False) - ] - , field "inputFields" $ list $ nonNull typeInputValue + & typeWithDeprecatedFilter + , field "inputFields" (list $ nonNull typeInputValue) + & typeWithDeprecatedFilter , field "ofType" typeIntrospectionType ] & withDescription @@ -636,7 +684,11 @@ typeDirective = "__Directive" [ field "name" $ nonNull typeString , field "description" typeString - , field "args" $ nonNull $ list $ nonNull typeInputValue + , field "args" (nonNull $ list $ nonNull typeInputValue) + & withArguments + [ inputValue "includeDeprecated" typeBool + & withDefaultValue (toGraphQL False) + ] , field "isRepeatable" $ nonNull typeBool , field "locations" $ nonNull $ list $ nonNull typeDirectiveLocation ] @@ -700,3 +752,38 @@ typeDirectiveLocation = & withDescription "A Directive can be adjacent to many parts of the GraphQL language, \ \a __DirectiveLocation describes one such possible adjacencies." + + +-- Internal helper which adds custom logic to a resolver for handling the +-- `includeDeprecated` filter. +typeWithDeprecatedFilter :: Field -> Field +typeWithDeprecatedFilter Field{..} = + Field + { args = + args + <> [ inputValue "includeDeprecated" typeBool + & withDefaultValue (toGraphQL False) + ] + , customResolver = \case + Value.List values -> do + context <- ask + let + Value.Arguments gqlArgs = context.arguments + includeDeprecated = HashMap.lookup "includeDeprecated" gqlArgs + filtered = + if includeDeprecated == Just (Value.Boolean True) + then values + else + filter + ( \case + Value.Object fields -> + HashMap.lookup "isDeprecated" fields + /= Just (Value.Boolean True) + _ -> True + ) + values + + customResolver $ Value.List filtered + o -> customResolver o + , .. + } diff --git a/tests/Tests/IntrospectionSpec.hs b/tests/Tests/IntrospectionSpec.hs index e47cde8..bf88ef7 100644 --- a/tests/Tests/IntrospectionSpec.hs +++ b/tests/Tests/IntrospectionSpec.hs @@ -101,7 +101,7 @@ main = void $ do { "name": "users", "args": [ - { "name": "filter", + { "name": "where", "type": { "name": "users_filter" } }, { "name": "order_by", @@ -118,7 +118,7 @@ main = void $ do { "name": "songs", "args": [ - { "name": "filter", + { "name": "where", "type": { "name": "songs_filter" } }, { "name": "order_by", @@ -235,20 +235,20 @@ main = void $ do { "name": "update_users", "args": [ - { "name": "filter" }, - { "name": "set" } + { "name": "where" }, + { "name": "_set" } ] }, { "name": "update_users_by_pk", "args": [ { "name": "email" }, - { "name": "set" } + { "name": "_set" } ] }, { "name": "delete_users", - "args": [ { "name": "filter" } ] + "args": [ { "name": "where" } ] }, { "name": "delete_users_by_pk", @@ -261,20 +261,20 @@ main = void $ do { "name": "update_songs", "args": [ - { "name": "filter" }, - { "name": "set" } + { "name": "where" }, + { "name": "_set" } ] }, { "name": "update_songs_by_pk", "args": [ { "name": "rowid" }, - { "name": "set" } + { "name": "_set" } ] }, { "name": "delete_songs", - "args": [ { "name": "filter" } ] + "args": [ { "name": "where" } ] }, { "name": "delete_songs_by_pk", @@ -626,8 +626,8 @@ main = void $ do Right result <- graphql schema Nothing mempty introspectionQuery -- Uncomment to write the new file to disk (for easier diffing) - -- writeFile (testRoot </> "new_introspection_result.json") $ - -- decodeUtf8 $ + -- P.writeFile (testRoot </> "new_introspection_result.json") $ + -- P.decodeUtf8 $ -- BL.toStrict $ -- Ae.encode result @@ -775,7 +775,7 @@ main = void $ do it "appends _ at the end of argument names to avoid conflicts" $ do let dbName = "by-pk-arg-names.db" withTestDbConn dbName $ \conn -> do - SS.execute_ conn [sql| CREATE TABLE foo ("set" INT PRIMARY KEY) |] + SS.execute_ conn [sql| CREATE TABLE foo ("_set" INT PRIMARY KEY) |] let introspectionQuery = @@ -804,24 +804,24 @@ main = void $ do { "name": "update_foo", "args": [ - { "name": "set" }, - { "name": "filter" } + { "name": "_set" }, + { "name": "where" } ] }, { "name": "update_foo_by_pk", "args": [ - { "name": "set" }, - { "name": "set_" } + { "name": "_set" }, + { "name": "_set_" } ] }, { "name": "delete_foo", - "args": [{ "name": "filter" }] + "args": [{ "name": "where" }] }, { "name": "delete_foo_by_pk", - "args": [{ "name": "set" }] + "args": [{ "name": "_set" }] } ] } diff --git a/tests/Tests/Utils.hs b/tests/Tests/Utils.hs index 1b6fd7a..6cc1edd 100644 --- a/tests/Tests/Utils.hs +++ b/tests/Tests/Utils.hs @@ -54,7 +54,7 @@ dbPath = testRoot </> "fixture.db" -- but some functions still take database IDs as arguments. -- Example usages include: -- - Including the ID in error messages --- - Generating a URL where the user can access a file when it's cell needs +-- - Generating a URL where the user can access a file when its cell needs -- to be converted to GraphQL -- -- Those usages don't matter when testing, so we use a dummy ID instead. diff --git a/tests/introspection_result.json b/tests/introspection_result.json index e733f05..5138157 100644 --- a/tests/introspection_result.json +++ b/tests/introspection_result.json @@ -1,2969 +1 @@ -{ - "data": { - "__schema": { - "directives": [ - { - "args": [ - { - "defaultValue": null, - "description": "Skipped when true.", - "name": "if", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - } - ], - "description": "Directs the executor to skip this field or fragment when the `if` argument is true.", - "locations": [ - "INLINE_FRAGMENT", - "FRAGMENT_SPREAD", - "FIELD" - ], - "name": "skip" - }, - { - "args": [ - { - "defaultValue": null, - "description": "Included when true.", - "name": "if", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - } - ], - "description": "Directs the executor to include this field or fragment only when the `if` argument is true.", - "locations": [ - "INLINE_FRAGMENT", - "FRAGMENT_SPREAD", - "FIELD" - ], - "name": "include" - } - ], - "mutationType": { - "name": "Mutation" - }, - "queryType": { - "name": "Query" - }, - "subscriptionType": null, - "types": [ - { - "description": "Object and Interface types are described by a list of Fields, each of which has a name, potentially a list of arguments, and a return type.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "args", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__InputValue", - "ofType": null - } - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "type", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "isDeprecated", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "deprecationReason", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__Field", - "possibleTypes": null - }, - { - "description": "A Directive can be adjacent to many parts of the GraphQL language, a __DirectiveLocation describes one such possible adjacencies.", - "enumValues": [ - { - "deprecationReason": null, - "description": "Location adjacent to a query operation.", - "isDeprecated": false, - "name": "QUERY" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a mutation operation.", - "isDeprecated": false, - "name": "MUTATION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a subscription operation.", - "isDeprecated": false, - "name": "SUBSCRIPTION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a field.", - "isDeprecated": false, - "name": "FIELD" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a fragment definition.", - "isDeprecated": false, - "name": "FRAGMENT_DEFINITION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a fragment spread.", - "isDeprecated": false, - "name": "FRAGMENT_SPREAD" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an inline fragment.", - "isDeprecated": false, - "name": "INLINE_FRAGMENT" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a variable definition.", - "isDeprecated": false, - "name": "VARIABLE_DEFINITION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a schema definition.", - "isDeprecated": false, - "name": "SCHEMA" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a scalar definition.", - "isDeprecated": false, - "name": "SCALAR" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an object type definition.", - "isDeprecated": false, - "name": "OBJECT" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a field definition.", - "isDeprecated": false, - "name": "FIELD_DEFINITION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an argument definition.", - "isDeprecated": false, - "name": "ARGUMENT_DEFINITION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an interface definition.", - "isDeprecated": false, - "name": "INTERFACE" - }, - { - "deprecationReason": null, - "description": "Location adjacent to a union definition.", - "isDeprecated": false, - "name": "UNION" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an enum definition.", - "isDeprecated": false, - "name": "ENUM" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an enum value definition.", - "isDeprecated": false, - "name": "ENUM_VALUE" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an input object type definition.", - "isDeprecated": false, - "name": "INPUT_OBJECT" - }, - { - "deprecationReason": null, - "description": "Location adjacent to an input object field definition.", - "isDeprecated": false, - "name": "INPUT_FIELD_DEFINITION" - } - ], - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "ENUM", - "name": "__DirectiveLocation", - "possibleTypes": null - }, - { - "description": "Specifies how broken UNIQUE constraints for users should be handled", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": "columns to handle conflicts of", - "name": "constraint", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "users_column", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "columns to override on conflict", - "name": "update_columns", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "users_column", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "filter specifying which conflicting columns to update", - "name": "where", - "type": { - "kind": "INPUT_OBJECT", - "name": "users_filter", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "users_upsert_on_conflict", - "possibleTypes": null - }, - { - "description": "Mutation response for table \"users\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "affected_rows", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "returning", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_row", - "ofType": null - } - } - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "users_mutation_response", - "possibleTypes": null - }, - { - "description": "Select rows matching the provided filter object", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "INPUT_OBJECT", - "name": "IntComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "INPUT_OBJECT", - "name": "StringComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "duration_seconds", - "type": { - "kind": "INPUT_OBJECT", - "name": "IntComparison", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "songs_filter", - "possibleTypes": null - }, - { - "description": "A GraphQL Schema defines the capabilities of a GraphQL server. It exposes all available types and directives on the server, as well as the entry points for query, mutation, and subscription operations.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": "A list of all types supported by this server.", - "isDeprecated": false, - "name": "types", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": "The type that query operations will be rooted at.", - "isDeprecated": false, - "name": "queryType", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": "If this server supports mutation, the type that mutation operations will be rooted at.", - "isDeprecated": false, - "name": "mutationType", - "type": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": "If this server support subscription, the type that subscription operations will be rooted at.", - "isDeprecated": false, - "name": "subscriptionType", - "type": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": "A list of all directives supported by this server.", - "isDeprecated": false, - "name": "directives", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Directive", - "ofType": null - } - } - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__Schema", - "possibleTypes": null - }, - { - "description": "An enum describing what kind of type a given `__Type` is.", - "enumValues": [ - { - "deprecationReason": null, - "description": "Indicates this type is a scalar.", - "isDeprecated": false, - "name": "SCALAR" - }, - { - "deprecationReason": null, - "description": "Indicates this type is an object. `fields` and `interfaces` are valid fields.", - "isDeprecated": false, - "name": "OBJECT" - }, - { - "deprecationReason": null, - "description": "Indicates this type is an interface. `fields` and `possibleTypes` are valid fields.", - "isDeprecated": false, - "name": "INTERFACE" - }, - { - "deprecationReason": null, - "description": "Indicates this type is a union. `possibleTypes` is a valid field.", - "isDeprecated": false, - "name": "UNION" - }, - { - "deprecationReason": null, - "description": "Indicates this type is an enum. `enumValues` is a valid field.", - "isDeprecated": false, - "name": "ENUM" - }, - { - "deprecationReason": null, - "description": "Indicates this type is an input object. `inputFields` is a valid field.", - "isDeprecated": false, - "name": "INPUT_OBJECT" - }, - { - "deprecationReason": null, - "description": "Indicates this type is a list. `ofType` is a valid field.", - "isDeprecated": false, - "name": "LIST" - }, - { - "deprecationReason": null, - "description": "Indicates this type is a non-null. `ofType` is a valid field.", - "isDeprecated": false, - "name": "NON_NULL" - } - ], - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "ENUM", - "name": "__TypeKind", - "possibleTypes": null - }, - { - "description": "Ordering options when selecting data from \"users\".", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "created_utc", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "number_of_logins", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "progress", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "users_order_by", - "possibleTypes": null - }, - { - "description": "The fundamental unit of any GraphQL Schema is the type. There are many kinds of types in GraphQL as represented by the `__TypeKind` enum.\n\nDepending on the kind of a type, certain fields describe information about that type. Scalar types provide no information beyond a name and description, while Enum types provide their values. Object and Interface types provide the fields they describe. Abstract types, Union and Interface, provide the Object types possible at runtime. List and NonNull types compose other types.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "kind", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "__TypeKind", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "interfaces", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "possibleTypes", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - } - }, - { - "args": [ - { - "defaultValue": "False", - "description": null, - "name": "includeDeprecated", - "type": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - ], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "fields", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Field", - "ofType": null - } - } - } - }, - { - "args": [ - { - "defaultValue": "False", - "description": null, - "name": "includeDeprecated", - "type": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - ], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "enumValues", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__EnumValue", - "ofType": null - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "inputFields", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__InputValue", - "ofType": null - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "ofType", - "type": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__Type", - "possibleTypes": null - }, - { - "description": "Ordering options when selecting data from \"songs\".", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "duration_seconds", - "type": { - "kind": "ENUM", - "name": "OrderingTerm", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "songs_order_by", - "possibleTypes": null - }, - { - "description": "Compare to a(n) Float", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "eq", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "neq", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gt", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gte", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lt", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lte", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "like", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "ilike", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "in", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "nin", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "FloatComparison", - "possibleTypes": null - }, - { - "description": "Available columns for table \"songs\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "rowid", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "duration_seconds", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "songs_row", - "possibleTypes": null - }, - { - "description": "This enum contains a variant for each column in the table", - "enumValues": [ - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "rowid" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "email" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "created_utc" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "number_of_logins" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "progress" - } - ], - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "ENUM", - "name": "users_column", - "possibleTypes": null - }, - { - "description": "The `Boolean` scalar type represents `true` or `false`.", - "enumValues": null, - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "SCALAR", - "name": "Boolean", - "possibleTypes": null - }, - { - "description": "Ordering options when ordering by a column", - "enumValues": [ - { - "deprecationReason": null, - "description": "In ascending order", - "isDeprecated": false, - "name": "ASC" - }, - { - "deprecationReason": "GraphQL spec recommends all caps for enums", - "description": "In ascending order", - "isDeprecated": true, - "name": "asc" - }, - { - "deprecationReason": null, - "description": "In descending order", - "isDeprecated": false, - "name": "DESC" - }, - { - "deprecationReason": "GraphQL spec recommends all caps for enums", - "description": "In descending order", - "isDeprecated": true, - "name": "desc" - } - ], - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "ENUM", - "name": "OrderingTerm", - "possibleTypes": null - }, - { - "description": "Arguments provided to Fields or Directives and the input fields of an InputObject are represented as Input Values which describe their type and optionally a default value.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "type", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__Type", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": "A GraphQL-formatted string representing the default value for this input value.", - "isDeprecated": false, - "name": "defaultValue", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__InputValue", - "possibleTypes": null - }, - { - "description": "Input object for songs", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "duration_seconds", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "songs_insert_input", - "possibleTypes": null - }, - { - "description": "Specifies how broken UNIQUE constraints for songs should be handled", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": "columns to handle conflicts of", - "name": "constraint", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "songs_column", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "columns to override on conflict", - "name": "update_columns", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "songs_column", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "filter specifying which conflicting columns to update", - "name": "where", - "type": { - "kind": "INPUT_OBJECT", - "name": "songs_filter", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "songs_upsert_on_conflict", - "possibleTypes": null - }, - { - "description": null, - "enumValues": null, - "fields": [ - { - "args": [ - { - "defaultValue": null, - "description": "Rows to be inserted", - "name": "objects", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_insert_input", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "Specifies how to handle broken UNIQUE constraints", - "name": "on_conflict", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_upsert_on_conflict", - "ofType": null - } - } - } - } - ], - "deprecationReason": null, - "description": "Insert new rows in table \"users\"", - "isDeprecated": false, - "name": "insert_users", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Rows to be inserted", - "name": "objects", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_insert_input", - "ofType": null - } - } - } - } - }, - { - "defaultValue": null, - "description": "Specifies how to handle broken UNIQUE constraints", - "name": "on_conflict", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_upsert_on_conflict", - "ofType": null - } - } - } - } - ], - "deprecationReason": null, - "description": "Insert new rows in table \"songs\"", - "isDeprecated": false, - "name": "insert_songs", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Fields to be updated", - "name": "set", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_set_input", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": "Filter to select rows to be updated", - "name": "filter", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_filter", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Update rows in table \"users\"", - "isDeprecated": false, - "name": "update_users", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Fields to be updated", - "name": "set", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_set_input", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": "Filter to select rows to be updated", - "name": "filter", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_filter", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Update rows in table \"songs\"", - "isDeprecated": false, - "name": "update_songs", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Filter to select rows to be deleted", - "name": "filter", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_filter", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Delete rows in table \"users\"", - "isDeprecated": false, - "name": "delete_users", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Filter to select rows to be deleted", - "name": "filter", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_filter", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Delete rows in table \"songs\"", - "isDeprecated": false, - "name": "delete_songs", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_mutation_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Fields to be updated", - "name": "set", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_set_input", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Update row in table \"users\" by PK", - "isDeprecated": false, - "name": "update_users_by_pk", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_mutation_by_pk_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Fields to be updated", - "name": "set", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_set_input", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Update row in table \"songs\" by PK", - "isDeprecated": false, - "name": "update_songs_by_pk", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_mutation_by_pk_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Delete row in table \"users\" by PK", - "isDeprecated": false, - "name": "delete_users_by_pk", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_mutation_by_pk_response", - "ofType": null - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Delete row in table \"songs\" by PK", - "isDeprecated": false, - "name": "delete_songs_by_pk", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_mutation_by_pk_response", - "ofType": null - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "Mutation", - "possibleTypes": null - }, - { - "description": "Data type for column 'name'", - "enumValues": null, - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "SCALAR", - "name": "String", - "possibleTypes": null - }, - { - "description": "Select rows matching the provided filter object", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "INPUT_OBJECT", - "name": "IntComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "INPUT_OBJECT", - "name": "StringComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "INPUT_OBJECT", - "name": "StringComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "created_utc", - "type": { - "kind": "INPUT_OBJECT", - "name": "StringComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "number_of_logins", - "type": { - "kind": "INPUT_OBJECT", - "name": "IntComparison", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "progress", - "type": { - "kind": "INPUT_OBJECT", - "name": "FloatComparison", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "users_filter", - "possibleTypes": null - }, - { - "description": "Data type for column 'progress'", - "enumValues": null, - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "SCALAR", - "name": "Float", - "possibleTypes": null - }, - { - "description": "A Directive provides a way to describe alternate runtime execution and type validation behavior in a GraphQL document.\n\nIn some cases, you need to provide options to alter GraphQL's execution behavior in ways field arguments will not suffice, such as conditionally including or skipping a field. Directives provide this by describing additional information to the executor.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "args", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "__InputValue", - "ofType": null - } - } - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "isRepeatable", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "locations", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "ENUM", - "name": "__DirectiveLocation", - "ofType": null - } - } - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__Directive", - "possibleTypes": null - }, - { - "description": "The `ID` scalar type represents a unique identifier, often used to refetch an object or as key for a cache. The ID type appears in a JSON response as a String; however, it is not intended to be human-readable. When expected as an input type, any string (such as `\"4\"`) or integer (such as `4`) input value will be accepted as an ID.", - "enumValues": null, - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "SCALAR", - "name": "ID", - "possibleTypes": null - }, - { - "description": "This enum contains a variant for each column in the table", - "enumValues": [ - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "rowid" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name" - }, - { - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "duration_seconds" - } - ], - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "ENUM", - "name": "songs_column", - "possibleTypes": null - }, - { - "description": "Fields to set for users", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "created_utc", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "number_of_logins", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "progress", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "users_set_input", - "possibleTypes": null - }, - { - "description": "Fields to set for songs", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "duration_seconds", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "songs_set_input", - "possibleTypes": null - }, - { - "description": "Response for a PK-based mutation on table \"users\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "affected_rows", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "returning", - "type": { - "kind": "OBJECT", - "name": "users_row", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "users_mutation_by_pk_response", - "possibleTypes": null - }, - { - "description": "One possible value for a given Enum. Enum values are unique values, not a placeholder for a string or numeric value. However an Enum value is returned in a JSON response as a string.", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "description", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "isDeprecated", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Boolean", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "deprecationReason", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "__EnumValue", - "possibleTypes": null - }, - { - "description": "Compare to a(n) Int", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "eq", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "neq", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gt", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gte", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lt", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lte", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "like", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "ilike", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "in", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "nin", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "IntComparison", - "possibleTypes": null - }, - { - "description": "Mutation response for table \"songs\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "affected_rows", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "returning", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_row", - "ofType": null - } - } - } - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "songs_mutation_response", - "possibleTypes": null - }, - { - "description": "Data type for column 'rowid'", - "enumValues": null, - "fields": null, - "inputFields": null, - "interfaces": null, - "kind": "SCALAR", - "name": "Int", - "possibleTypes": null - }, - { - "description": "Compare to a(n) String", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "eq", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "neq", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gt", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "gte", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lt", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "lte", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "like", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "ilike", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "in", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "nin", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "StringComparison", - "possibleTypes": null - }, - { - "description": "Input object for users", - "enumValues": null, - "fields": null, - "inputFields": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "name", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "created_utc", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": null, - "name": "number_of_logins", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": null, - "name": "progress", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - } - ], - "interfaces": null, - "kind": "INPUT_OBJECT", - "name": "users_insert_input", - "possibleTypes": null - }, - { - "description": "Response for a PK-based mutation on table \"songs\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "affected_rows", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "returning", - "type": { - "kind": "OBJECT", - "name": "songs_row", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "songs_mutation_by_pk_response", - "possibleTypes": null - }, - { - "description": null, - "enumValues": null, - "fields": [ - { - "args": [ - { - "defaultValue": null, - "description": "Filter to select specific rows", - "name": "filter", - "type": { - "kind": "INPUT_OBJECT", - "name": "users_filter", - "ofType": null - } - }, - { - "defaultValue": null, - "description": "Columns used to sort the data", - "name": "order_by", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "users_order_by", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": "Limit the number of returned rows", - "name": "limit", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": "The index to start returning rows from", - "name": "offset", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - ], - "deprecationReason": null, - "description": "Rows from the table \"users\"", - "isDeprecated": false, - "name": "users", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "users_row", - "ofType": null - } - } - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": "Filter to select specific rows", - "name": "filter", - "type": { - "kind": "INPUT_OBJECT", - "name": "songs_filter", - "ofType": null - } - }, - { - "defaultValue": null, - "description": "Columns used to sort the data", - "name": "order_by", - "type": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "INPUT_OBJECT", - "name": "songs_order_by", - "ofType": null - } - } - }, - { - "defaultValue": null, - "description": "Limit the number of returned rows", - "name": "limit", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "defaultValue": null, - "description": "The index to start returning rows from", - "name": "offset", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - ], - "deprecationReason": null, - "description": "Rows from the table \"songs\"", - "isDeprecated": false, - "name": "songs", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "LIST", - "name": null, - "ofType": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "OBJECT", - "name": "songs_row", - "ofType": null - } - } - } - } - }, - { - "args": [ - { - "defaultValue": null, - "description": null, - "name": "email", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Rows from the table \"users\", accessible by their primary key", - "isDeprecated": false, - "name": "users_by_pk", - "type": { - "kind": "OBJECT", - "name": "users_row", - "ofType": null - } - }, - { - "args": [ - { - "defaultValue": null, - "description": null, - "name": "rowid", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - } - ], - "deprecationReason": null, - "description": "Rows from the table \"songs\", accessible by their primary key", - "isDeprecated": false, - "name": "songs_by_pk", - "type": { - "kind": "OBJECT", - "name": "songs_row", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "Query", - "possibleTypes": null - }, - { - "description": "Available columns for table \"users\"", - "enumValues": null, - "fields": [ - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "rowid", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "name", - "type": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "email", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "created_utc", - "type": { - "kind": "NON_NULL", - "name": null, - "ofType": { - "kind": "SCALAR", - "name": "String", - "ofType": null - } - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "number_of_logins", - "type": { - "kind": "SCALAR", - "name": "Int", - "ofType": null - } - }, - { - "args": [], - "deprecationReason": null, - "description": null, - "isDeprecated": false, - "name": "progress", - "type": { - "kind": "SCALAR", - "name": "Float", - "ofType": null - } - } - ], - "inputFields": null, - "interfaces": [], - "kind": "OBJECT", - "name": "users_row", - "possibleTypes": null - } - ] - } - } -} +{"data":{"__schema":{"directives":[{"args":[{"defaultValue":null,"description":"Skipped when true.","name":"if","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}}],"description":"Directs the executor to skip this field or fragment when the `if` argument is true.","locations":["INLINE_FRAGMENT","FRAGMENT_SPREAD","FIELD"],"name":"skip"},{"args":[{"defaultValue":null,"description":"Included when true.","name":"if","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}}],"description":"Directs the executor to include this field or fragment only when the `if` argument is true.","locations":["INLINE_FRAGMENT","FRAGMENT_SPREAD","FIELD"],"name":"include"}],"mutationType":{"name":"Mutation"},"queryType":{"name":"Query"},"subscriptionType":null,"types":[{"description":"Object and Interface types are described by a list of Fields, each of which has a name, potentially a list of arguments, and a return type.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[{"defaultValue":"False","description":null,"name":"includeDeprecated","type":{"kind":"SCALAR","name":"Boolean","ofType":null}}],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"args","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__InputValue","ofType":null}}}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"type","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"isDeprecated","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"deprecationReason","type":{"kind":"SCALAR","name":"String","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__Field","possibleTypes":null},{"description":"A Directive can be adjacent to many parts of the GraphQL language, a __DirectiveLocation describes one such possible adjacencies.","enumValues":[{"deprecationReason":null,"description":"Location adjacent to a query operation.","isDeprecated":false,"name":"QUERY"},{"deprecationReason":null,"description":"Location adjacent to a mutation operation.","isDeprecated":false,"name":"MUTATION"},{"deprecationReason":null,"description":"Location adjacent to a subscription operation.","isDeprecated":false,"name":"SUBSCRIPTION"},{"deprecationReason":null,"description":"Location adjacent to a field.","isDeprecated":false,"name":"FIELD"},{"deprecationReason":null,"description":"Location adjacent to a fragment definition.","isDeprecated":false,"name":"FRAGMENT_DEFINITION"},{"deprecationReason":null,"description":"Location adjacent to a fragment spread.","isDeprecated":false,"name":"FRAGMENT_SPREAD"},{"deprecationReason":null,"description":"Location adjacent to an inline fragment.","isDeprecated":false,"name":"INLINE_FRAGMENT"},{"deprecationReason":null,"description":"Location adjacent to a variable definition.","isDeprecated":false,"name":"VARIABLE_DEFINITION"},{"deprecationReason":null,"description":"Location adjacent to a schema definition.","isDeprecated":false,"name":"SCHEMA"},{"deprecationReason":null,"description":"Location adjacent to a scalar definition.","isDeprecated":false,"name":"SCALAR"},{"deprecationReason":null,"description":"Location adjacent to an object type definition.","isDeprecated":false,"name":"OBJECT"},{"deprecationReason":null,"description":"Location adjacent to a field definition.","isDeprecated":false,"name":"FIELD_DEFINITION"},{"deprecationReason":null,"description":"Location adjacent to an argument definition.","isDeprecated":false,"name":"ARGUMENT_DEFINITION"},{"deprecationReason":null,"description":"Location adjacent to an interface definition.","isDeprecated":false,"name":"INTERFACE"},{"deprecationReason":null,"description":"Location adjacent to a union definition.","isDeprecated":false,"name":"UNION"},{"deprecationReason":null,"description":"Location adjacent to an enum definition.","isDeprecated":false,"name":"ENUM"},{"deprecationReason":null,"description":"Location adjacent to an enum value definition.","isDeprecated":false,"name":"ENUM_VALUE"},{"deprecationReason":null,"description":"Location adjacent to an input object type definition.","isDeprecated":false,"name":"INPUT_OBJECT"},{"deprecationReason":null,"description":"Location adjacent to an input object field definition.","isDeprecated":false,"name":"INPUT_FIELD_DEFINITION"}],"fields":null,"inputFields":null,"interfaces":null,"kind":"ENUM","name":"__DirectiveLocation","possibleTypes":null},{"description":"Specifies how broken UNIQUE constraints for users should be handled","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":"columns to handle conflicts of","name":"constraint","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"users_column","ofType":null}}}}},{"defaultValue":null,"description":"columns to override on conflict","name":"update_columns","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"users_column","ofType":null}}}}},{"defaultValue":null,"description":"filter specifying which conflicting columns to update","name":"where","type":{"kind":"INPUT_OBJECT","name":"users_filter","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"users_upsert_on_conflict","possibleTypes":null},{"description":"Mutation response for table \"users\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"affected_rows","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"returning","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_row","ofType":null}}}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"users_mutation_response","possibleTypes":null},{"description":"Select rows matching the provided filter object","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"INPUT_OBJECT","name":"IntComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"INPUT_OBJECT","name":"StringComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"duration_seconds","type":{"kind":"INPUT_OBJECT","name":"IntComparison","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"songs_filter","possibleTypes":null},{"description":"A GraphQL Schema defines the capabilities of a GraphQL server. It exposes all available types and directives on the server, as well as the entry points for query, mutation, and subscription operations.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":"A list of all types supported by this server.","isDeprecated":false,"name":"types","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}}}},{"args":[],"deprecationReason":null,"description":"The type that query operations will be rooted at.","isDeprecated":false,"name":"queryType","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}},{"args":[],"deprecationReason":null,"description":"If this server supports mutation, the type that mutation operations will be rooted at.","isDeprecated":false,"name":"mutationType","type":{"kind":"OBJECT","name":"__Type","ofType":null}},{"args":[],"deprecationReason":null,"description":"If this server support subscription, the type that subscription operations will be rooted at.","isDeprecated":false,"name":"subscriptionType","type":{"kind":"OBJECT","name":"__Type","ofType":null}},{"args":[],"deprecationReason":null,"description":"A list of all directives supported by this server.","isDeprecated":false,"name":"directives","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Directive","ofType":null}}}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__Schema","possibleTypes":null},{"description":"An enum describing what kind of type a given `__Type` is.","enumValues":[{"deprecationReason":null,"description":"Indicates this type is a scalar.","isDeprecated":false,"name":"SCALAR"},{"deprecationReason":null,"description":"Indicates this type is an object. `fields` and `interfaces` are valid fields.","isDeprecated":false,"name":"OBJECT"},{"deprecationReason":null,"description":"Indicates this type is an interface. `fields` and `possibleTypes` are valid fields.","isDeprecated":false,"name":"INTERFACE"},{"deprecationReason":null,"description":"Indicates this type is a union. `possibleTypes` is a valid field.","isDeprecated":false,"name":"UNION"},{"deprecationReason":null,"description":"Indicates this type is an enum. `enumValues` is a valid field.","isDeprecated":false,"name":"ENUM"},{"deprecationReason":null,"description":"Indicates this type is an input object. `inputFields` is a valid field.","isDeprecated":false,"name":"INPUT_OBJECT"},{"deprecationReason":null,"description":"Indicates this type is a list. `ofType` is a valid field.","isDeprecated":false,"name":"LIST"},{"deprecationReason":null,"description":"Indicates this type is a non-null. `ofType` is a valid field.","isDeprecated":false,"name":"NON_NULL"}],"fields":null,"inputFields":null,"interfaces":null,"kind":"ENUM","name":"__TypeKind","possibleTypes":null},{"description":"Ordering options when selecting data from \"users\".","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"email","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"created_utc","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"number_of_logins","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"progress","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"users_order_by","possibleTypes":null},{"description":"The fundamental unit of any GraphQL Schema is the type. There are many kinds of types in GraphQL as represented by the `__TypeKind` enum.\n\nDepending on the kind of a type, certain fields describe information about that type. Scalar types provide no information beyond a name and description, while Enum types provide their values. Object and Interface types provide the fields they describe. Abstract types, Union and Interface, provide the Object types possible at runtime. List and NonNull types compose other types.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"kind","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"__TypeKind","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"interfaces","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"possibleTypes","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}}},{"args":[{"defaultValue":"False","description":null,"name":"includeDeprecated","type":{"kind":"SCALAR","name":"Boolean","ofType":null}}],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"fields","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Field","ofType":null}}}},{"args":[{"defaultValue":"False","description":null,"name":"includeDeprecated","type":{"kind":"SCALAR","name":"Boolean","ofType":null}}],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"enumValues","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__EnumValue","ofType":null}}}},{"args":[{"defaultValue":"False","description":null,"name":"includeDeprecated","type":{"kind":"SCALAR","name":"Boolean","ofType":null}}],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"inputFields","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__InputValue","ofType":null}}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"ofType","type":{"kind":"OBJECT","name":"__Type","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__Type","possibleTypes":null},{"description":"Ordering options when selecting data from \"songs\".","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}},{"defaultValue":null,"description":null,"name":"duration_seconds","type":{"kind":"ENUM","name":"OrderingTerm","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"songs_order_by","possibleTypes":null},{"description":"Compare to a(n) Float","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"_eq","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_neq","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_gt","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_gte","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_lt","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_lte","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_like","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_ilike","type":{"kind":"SCALAR","name":"Float","ofType":null}},{"defaultValue":null,"description":null,"name":"_in","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"Float","ofType":null}}},{"defaultValue":null,"description":null,"name":"_nin","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"Float","ofType":null}}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"FloatComparison","possibleTypes":null},{"description":"Available columns for table \"songs\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"rowid","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"duration_seconds","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"songs_row","possibleTypes":null},{"description":"This enum contains a variant for each column in the table","enumValues":[{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"rowid"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"email"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"created_utc"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"number_of_logins"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"progress"}],"fields":null,"inputFields":null,"interfaces":null,"kind":"ENUM","name":"users_column","possibleTypes":null},{"description":"The `Boolean` scalar type represents `true` or `false`.","enumValues":null,"fields":null,"inputFields":null,"interfaces":null,"kind":"SCALAR","name":"Boolean","possibleTypes":null},{"description":"Ordering options when ordering by a column","enumValues":[{"deprecationReason":null,"description":"In ascending order","isDeprecated":false,"name":"ASC"},{"deprecationReason":"GraphQL spec recommends all caps for enums","description":"In ascending order","isDeprecated":true,"name":"asc"},{"deprecationReason":null,"description":"In descending order","isDeprecated":false,"name":"DESC"},{"deprecationReason":"GraphQL spec recommends all caps for enums","description":"In descending order","isDeprecated":true,"name":"desc"}],"fields":null,"inputFields":null,"interfaces":null,"kind":"ENUM","name":"OrderingTerm","possibleTypes":null},{"description":"Arguments provided to Fields or Directives and the input fields of an InputObject are represented as Input Values which describe their type and optionally a default value.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"type","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__Type","ofType":null}}},{"args":[],"deprecationReason":null,"description":"A GraphQL-formatted string representing the default value for this input value.","isDeprecated":false,"name":"defaultValue","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"isDeprecated","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"deprecationReason","type":{"kind":"SCALAR","name":"String","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__InputValue","possibleTypes":null},{"description":"Input object for songs","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"defaultValue":null,"description":null,"name":"duration_seconds","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"songs_insert_input","possibleTypes":null},{"description":"Specifies how broken UNIQUE constraints for songs should be handled","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":"columns to handle conflicts of","name":"constraint","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"songs_column","ofType":null}}}}},{"defaultValue":null,"description":"columns to override on conflict","name":"update_columns","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"songs_column","ofType":null}}}}},{"defaultValue":null,"description":"filter specifying which conflicting columns to update","name":"where","type":{"kind":"INPUT_OBJECT","name":"songs_filter","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"songs_upsert_on_conflict","possibleTypes":null},{"description":null,"enumValues":null,"fields":[{"args":[{"defaultValue":null,"description":"Rows to be inserted","name":"objects","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"users_insert_input","ofType":null}}}}},{"defaultValue":null,"description":"Specifies how to handle broken UNIQUE constraints","name":"on_conflict","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"users_upsert_on_conflict","ofType":null}}}}],"deprecationReason":null,"description":"Insert new rows in table \"users\"","isDeprecated":false,"name":"insert_users","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":"Rows to be inserted","name":"objects","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"songs_insert_input","ofType":null}}}}},{"defaultValue":null,"description":"Specifies how to handle broken UNIQUE constraints","name":"on_conflict","type":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"songs_upsert_on_conflict","ofType":null}}}}],"deprecationReason":null,"description":"Insert new rows in table \"songs\"","isDeprecated":false,"name":"insert_songs","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":"Fields to be updated","name":"_set","type":{"kind":"INPUT_OBJECT","name":"users_set_input","ofType":null}},{"defaultValue":null,"description":"Filter to select rows to be updated","name":"where","type":{"kind":"INPUT_OBJECT","name":"users_filter","ofType":null}}],"deprecationReason":null,"description":"Update rows in table \"users\"","isDeprecated":false,"name":"update_users","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":"Fields to be updated","name":"_set","type":{"kind":"INPUT_OBJECT","name":"songs_set_input","ofType":null}},{"defaultValue":null,"description":"Filter to select rows to be updated","name":"where","type":{"kind":"INPUT_OBJECT","name":"songs_filter","ofType":null}}],"deprecationReason":null,"description":"Update rows in table \"songs\"","isDeprecated":false,"name":"update_songs","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":"Filter to select rows to be deleted","name":"where","type":{"kind":"INPUT_OBJECT","name":"users_filter","ofType":null}}],"deprecationReason":null,"description":"Delete rows in table \"users\"","isDeprecated":false,"name":"delete_users","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":"Filter to select rows to be deleted","name":"where","type":{"kind":"INPUT_OBJECT","name":"songs_filter","ofType":null}}],"deprecationReason":null,"description":"Delete rows in table \"songs\"","isDeprecated":false,"name":"delete_songs","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_mutation_response","ofType":null}}},{"args":[{"defaultValue":null,"description":null,"name":"email","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"defaultValue":null,"description":"Fields to be updated","name":"_set","type":{"kind":"INPUT_OBJECT","name":"users_set_input","ofType":null}}],"deprecationReason":null,"description":"Update row in table \"users\" by PK","isDeprecated":false,"name":"update_users_by_pk","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_mutation_by_pk_response","ofType":null}}},{"args":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"defaultValue":null,"description":"Fields to be updated","name":"_set","type":{"kind":"INPUT_OBJECT","name":"songs_set_input","ofType":null}}],"deprecationReason":null,"description":"Update row in table \"songs\" by PK","isDeprecated":false,"name":"update_songs_by_pk","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_mutation_by_pk_response","ofType":null}}},{"args":[{"defaultValue":null,"description":null,"name":"email","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}}],"deprecationReason":null,"description":"Delete row in table \"users\" by PK","isDeprecated":false,"name":"delete_users_by_pk","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_mutation_by_pk_response","ofType":null}}},{"args":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}}],"deprecationReason":null,"description":"Delete row in table \"songs\" by PK","isDeprecated":false,"name":"delete_songs_by_pk","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_mutation_by_pk_response","ofType":null}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"Mutation","possibleTypes":null},{"description":"Data type for column 'name'","enumValues":null,"fields":null,"inputFields":null,"interfaces":null,"kind":"SCALAR","name":"String","possibleTypes":null},{"description":"Select rows matching the provided filter object","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"INPUT_OBJECT","name":"IntComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"INPUT_OBJECT","name":"StringComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"email","type":{"kind":"INPUT_OBJECT","name":"StringComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"created_utc","type":{"kind":"INPUT_OBJECT","name":"StringComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"number_of_logins","type":{"kind":"INPUT_OBJECT","name":"IntComparison","ofType":null}},{"defaultValue":null,"description":null,"name":"progress","type":{"kind":"INPUT_OBJECT","name":"FloatComparison","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"users_filter","possibleTypes":null},{"description":"Data type for column 'progress'","enumValues":null,"fields":null,"inputFields":null,"interfaces":null,"kind":"SCALAR","name":"Float","possibleTypes":null},{"description":"A Directive provides a way to describe alternate runtime execution and type validation behavior in a GraphQL document.\n\nIn some cases, you need to provide options to alter GraphQL's execution behavior in ways field arguments will not suffice, such as conditionally including or skipping a field. Directives provide this by describing additional information to the executor.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[{"defaultValue":"False","description":null,"name":"includeDeprecated","type":{"kind":"SCALAR","name":"Boolean","ofType":null}}],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"args","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"__InputValue","ofType":null}}}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"isRepeatable","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"locations","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"ENUM","name":"__DirectiveLocation","ofType":null}}}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__Directive","possibleTypes":null},{"description":"The `ID` scalar type represents a unique identifier, often used to refetch an object or as key for a cache. The ID type appears in a JSON response as a String; however, it is not intended to be human-readable. When expected as an input type, any string (such as `\"4\"`) or integer (such as `4`) input value will be accepted as an ID.","enumValues":null,"fields":null,"inputFields":null,"interfaces":null,"kind":"SCALAR","name":"ID","possibleTypes":null},{"description":"This enum contains a variant for each column in the table","enumValues":[{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"rowid"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name"},{"deprecationReason":null,"description":null,"isDeprecated":false,"name":"duration_seconds"}],"fields":null,"inputFields":null,"interfaces":null,"kind":"ENUM","name":"songs_column","possibleTypes":null},{"description":"Fields to set for users","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"email","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"created_utc","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"number_of_logins","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"progress","type":{"kind":"SCALAR","name":"Float","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"users_set_input","possibleTypes":null},{"description":"Fields to set for songs","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"duration_seconds","type":{"kind":"SCALAR","name":"Int","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"songs_set_input","possibleTypes":null},{"description":"Response for a PK-based mutation on table \"users\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"affected_rows","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"returning","type":{"kind":"OBJECT","name":"users_row","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"users_mutation_by_pk_response","possibleTypes":null},{"description":"One possible value for a given Enum. Enum values are unique values, not a placeholder for a string or numeric value. However an Enum value is returned in a JSON response as a string.","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"description","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"isDeprecated","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Boolean","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"deprecationReason","type":{"kind":"SCALAR","name":"String","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"__EnumValue","possibleTypes":null},{"description":"Compare to a(n) Int","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"_eq","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_neq","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_gt","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_gte","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_lt","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_lte","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_like","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_ilike","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"_in","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"defaultValue":null,"description":null,"name":"_nin","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"IntComparison","possibleTypes":null},{"description":"Mutation response for table \"songs\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"affected_rows","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"returning","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_row","ofType":null}}}}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"songs_mutation_response","possibleTypes":null},{"description":"Data type for column 'rowid'","enumValues":null,"fields":null,"inputFields":null,"interfaces":null,"kind":"SCALAR","name":"Int","possibleTypes":null},{"description":"Compare to a(n) String","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"_eq","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_neq","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_gt","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_gte","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_lt","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_lte","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_like","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_ilike","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"_in","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"defaultValue":null,"description":null,"name":"_nin","type":{"kind":"LIST","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"StringComparison","possibleTypes":null},{"description":"Input object for users","enumValues":null,"fields":null,"inputFields":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"name","type":{"kind":"SCALAR","name":"String","ofType":null}},{"defaultValue":null,"description":null,"name":"email","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"defaultValue":null,"description":null,"name":"created_utc","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"defaultValue":null,"description":null,"name":"number_of_logins","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":null,"name":"progress","type":{"kind":"SCALAR","name":"Float","ofType":null}}],"interfaces":null,"kind":"INPUT_OBJECT","name":"users_insert_input","possibleTypes":null},{"description":"Response for a PK-based mutation on table \"songs\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"affected_rows","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"returning","type":{"kind":"OBJECT","name":"songs_row","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"songs_mutation_by_pk_response","possibleTypes":null},{"description":null,"enumValues":null,"fields":[{"args":[{"defaultValue":null,"description":"Filter to select specific rows","name":"where","type":{"kind":"INPUT_OBJECT","name":"users_filter","ofType":null}},{"defaultValue":null,"description":"Columns used to sort the data","name":"order_by","type":{"kind":"LIST","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"users_order_by","ofType":null}}},{"defaultValue":null,"description":"Limit the number of returned rows","name":"limit","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":"The index to start returning rows from","name":"offset","type":{"kind":"SCALAR","name":"Int","ofType":null}}],"deprecationReason":null,"description":"Rows from the table \"users\"","isDeprecated":false,"name":"users","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"users_row","ofType":null}}}}},{"args":[{"defaultValue":null,"description":"Filter to select specific rows","name":"where","type":{"kind":"INPUT_OBJECT","name":"songs_filter","ofType":null}},{"defaultValue":null,"description":"Columns used to sort the data","name":"order_by","type":{"kind":"LIST","name":null,"ofType":{"kind":"INPUT_OBJECT","name":"songs_order_by","ofType":null}}},{"defaultValue":null,"description":"Limit the number of returned rows","name":"limit","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"defaultValue":null,"description":"The index to start returning rows from","name":"offset","type":{"kind":"SCALAR","name":"Int","ofType":null}}],"deprecationReason":null,"description":"Rows from the table \"songs\"","isDeprecated":false,"name":"songs","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"LIST","name":null,"ofType":{"kind":"NON_NULL","name":null,"ofType":{"kind":"OBJECT","name":"songs_row","ofType":null}}}}},{"args":[{"defaultValue":null,"description":null,"name":"email","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}}],"deprecationReason":null,"description":"Rows from the table \"users\", accessible by their primary key","isDeprecated":false,"name":"users_by_pk","type":{"kind":"OBJECT","name":"users_row","ofType":null}},{"args":[{"defaultValue":null,"description":null,"name":"rowid","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}}],"deprecationReason":null,"description":"Rows from the table \"songs\", accessible by their primary key","isDeprecated":false,"name":"songs_by_pk","type":{"kind":"OBJECT","name":"songs_row","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"Query","possibleTypes":null},{"description":"Available columns for table \"users\"","enumValues":null,"fields":[{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"rowid","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"Int","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"name","type":{"kind":"SCALAR","name":"String","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"email","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"created_utc","type":{"kind":"NON_NULL","name":null,"ofType":{"kind":"SCALAR","name":"String","ofType":null}}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"number_of_logins","type":{"kind":"SCALAR","name":"Int","ofType":null}},{"args":[],"deprecationReason":null,"description":null,"isDeprecated":false,"name":"progress","type":{"kind":"SCALAR","name":"Float","ofType":null}}],"inputFields":null,"interfaces":[],"kind":"OBJECT","name":"users_row","possibleTypes":null}]}}}