Code Monkey home page Code Monkey logo

graphql-meta's Introduction

graphql-meta

A GraphQL toolkit providing the following:

  • Alex Lexer of the GraphQL lexical specification.
  • Happy Parser of the GraphQL BNF Grammar.
  • Pretty printer of the GraphQL abstract syntax tree (AST) for human consumption.
  • QuickCheck generators for creating random AST fragments
    • Used in conjunction with pretty printing to establish round trip property tests.
    • Source
  • Generics implementation providing correct-by-construction Schema at compile time.
  • QuasiQuoter providing inline definitions of ExecutableDefinitions.

Table of Contents

Query

{-# LANGUAGE QuasiQuotes #-}

module Main (main) where

import GraphQL.QQ (query)

main :: IO ()
main = print [query| { building (id: 123) {floorCount, id}} |]

Result

QueryDocument {getDefinitions = [
  DefinitionOperation (AnonymousQuery [
	SelectionField (Field Nothing (Name {unName = "building"}) [
	  Argument (Name {unName = "id"}) (ValueInt 123)] [] [
	SelectionField (Field Nothing (Name {unName = "floorCount"}) [] [] [])
	  , SelectionField (Field Nothing (Name {unName = "id"}) [] [] [])
	  ])
	])
  ]}

Substitution

GraphQL ExecutableDefinition abstract syntax tree rewriting is made possible via Template Haskell's metavariable substitution. During QuasiQuotation all unbound variables in a GraphQL query that have identical names inside the current scope will automatically be translated into GraphQL AST terms and substituted.

buildingQuery
  :: Int
  -> ExecutableDefinition
buildingQuery buildingId =
  [query| { building (id: $buildingId) {floorCount, id}} |]

Result

QueryDocument {getDefinitions = [
  DefinitionOperation (AnonymousQuery [
	SelectionField (Field Nothing (Name {unName = "building"}) [
	  Argument (Name {unName = "buildingId"}) (ValueInt 4)] [] [
	SelectionField (Field Nothing (Name {unName = "floorCount"}) [] [] [])
	  , SelectionField (Field Nothing (Name {unName = "id"}) [] [] [])
	  ])
	])
  ]}

Generics

It is possible to derive GraphQL schema using GHC.Generics. Simply import GHC.Generics, derive Generic (must enable the DeriveGeneric language extension) and make an instance of ToObjectTypeDefintion. See below for an example:

{-# LANGUAGE DeriveGeneric #-}

module Main where

import           GHC.Generics                    (Generic)
import           GraphQL.Internal.Syntax.Encoder (schemaDocument)
import           Data.Proxy                      (Proxy)
import qualified Data.Text.IO                    as T
import           GraphQL.Generic                 (ToObjectTypeDefinition(..))

data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Show, Eq, Generic)

instance ToObjectTypeDefinition Person

showPersonSchema :: IO ()
showPersonSchema = print $ toObjectTypeDefinition (Proxy @ Person)

-- type Person{name:String!,age:Int!}

Limitations

  • Generic deriving is currently only supported on product types with record field selectors.
  • Only ObjectTypeDefintion is currently supported.

Roadmap

  • Generic deriving of ScalarTypeDefintion and EnumTypeDefintion.

Maintainers

Credit

License

BSD3 2018-2019 Urbint Inc.

graphql-meta's People

Contributors

dmjio avatar russmatney avatar

Watchers

 avatar

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.