morpheus-graphql: Morpheus GraphQL

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Build GraphQL APIs with your favourite functional language!


[Skip to Readme]

Properties

Versions 0.0.1, 0.1.0, 0.1.1, 0.2.0, 0.2.1, 0.2.2, 0.3.0, 0.3.1, 0.4.0, 0.5.0, 0.6.0, 0.6.1, 0.6.2, 0.7.0, 0.7.1, 0.8.0, 0.9.0, 0.9.1, 0.10.0, 0.11.0, 0.11.0, 0.12.0, 0.13.0, 0.14.0, 0.14.1, 0.15.0, 0.15.1, 0.16.0, 0.17.0, 0.18.0, 0.19.0, 0.19.1, 0.19.2, 0.19.3, 0.20.0, 0.20.1, 0.21.0, 0.22.0, 0.22.1, 0.23.0, 0.24.0, 0.24.1, 0.24.2, 0.24.3, 0.25.0, 0.26.0, 0.27.0, 0.27.1, 0.27.2, 0.27.3
Change log changelog.md
Dependencies aeson (>=1.4.4.0 && <=1.6), base (>=4.7 && <5), bytestring (>=0.10.4 && <0.11), containers (>=0.4.2.1 && <0.7), megaparsec (>=7.0.0 && <9.0.0), mtl (>=2.0 && <=2.3), scientific (>=0.3.6.2 && <0.4), template-haskell (>=2.0 && <=2.16), text (>=1.2.3.0 && <1.3), th-lift-instances (>=0.1.1 && <=0.2.0), transformers (>=0.3.0.0 && <0.6), unliftio-core (>=0.0.1 && <=0.3), unordered-containers (>=0.2.8.0 && <0.3), uuid (>=1.0 && <=1.4), vector (>=0.12.0.1 && <0.13), websockets (>=0.11.0 && <=0.13) [details]
License MIT
Copyright (c) 2019 Daviti Nalchevanidze
Author Daviti Nalchevanidze
Maintainer d.nalchevanidze@gmail.com
Category web, graphql
Home page https://morpheusgraphql.com
Bug tracker https://github.com/nalchevanidze/morpheus-graphql/issues
Source repo head: git clone https://github.com/nalchevanidze/morpheus-graphql
Uploaded by nalchevanidze at 2020-05-01T09:18:05Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for morpheus-graphql-0.11.0

[back to package description]

Morpheus GraphQL Hackage CircleCI

Build GraphQL APIs with your favourite functional language!

Morpheus GraphQL (Server & Client) helps you to build GraphQL APIs in Haskell with native Haskell types. Morpheus will convert your Haskell types to a GraphQL schema and all your resolvers are just native Haskell functions. Mopheus GraphQL can also convert your GraphQL Schema or Query to Haskell types and validate them in compile time.

Morpheus is still in an early stage of development, so any feedback is more than welcome, and we appreciate any contribution! Just open an issue here on GitHub, or join our Slack channel to get in touch.

Getting Started

Setup

To get started with Morpheus, you first need to add it to your project's dependencies, as follows (assuming you're using hpack):

package.yml

dependencies:
  - morpheus-graphql

Additionally, you should tell stack which version to pick:

stack.yml

resolver: lts-14.8

extra-deps:
  - morpheus-graphql-0.11.0

As Morpheus is quite new, make sure stack can find morpheus-graphql by running stack upgrade and stack update

Building your first GraphQL API

with GraphQL syntax

schema.gql

type Query {
  deity(name: String!): Deity!
}

"""
Description for Deity
"""
type Deity {
  """
  Description for name
  """
  name: String!
  power: String @deprecated(reason: "some reason for")
}

API.hs

{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns        #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TemplateHaskell       #-}
{-# LANGUAGE TypeFamilies          #-}

module API (api) where

import qualified Data.ByteString.Lazy.Char8 as B

import           Data.Morpheus              (interpreter)
import           Data.Morpheus.Document     (importGQLDocumentWithNamespace)
import           Data.Morpheus.Types        (GQLRootResolver (..), IORes, Undefined(..))
import           Data.Text                  (Text)

importGQLDocumentWithNamespace "schema.gql"

rootResolver :: GQLRootResolver IO () Query Undefined Undefined
rootResolver =
  GQLRootResolver
    {
      queryResolver = Query {queryDeity},
      mutationResolver = Undefined,
      subscriptionResolver = Undefined
    }
  where
    queryDeity QueryDeityArgs {queryDeityArgsName} = pure Deity
      {
        deityName = pure "Morpheus"
      , deityPower = pure (Just "Shapeshifting")
      }

api :: ByteString -> IO ByteString
api = interpreter rootResolver

Template Haskell Generates types: Query , Deity, DeityArgs, that can be used by rootResolver

descriptions and deprecations will be displayed in introspection.

importGQLDocumentWithNamespace will generate Types with namespaced fields. If you don't need napespacing use importGQLDocument

with Native Haskell Types

To define a GraphQL API with Morpheus we start by defining the API Schema as a native Haskell data type, which derives the Generic typeclass. Lazily resolvable fields on this Query type are defined via a -> IORes b, representing resolving a set of arguments a to a concrete value b.

data Query m = Query
  { deity :: DeityArgs -> m Deity
  } deriving (Generic, GQLType)

data Deity = Deity
  { fullName :: Text         -- Non-Nullable Field
  , power    :: Maybe Text   -- Nullable Field
  } deriving (Generic,GQLType)

data DeityArgs = DeityArgs
  { name      :: Text        -- Required Argument
  , mythology :: Maybe Text  -- Optional Argument
  } deriving (Generic)

For each field in the Query type defined via a -> m b (like deity) we will define a resolver implementation that provides the values during runtime by referring to some data source, e.g. a database or another API. Fields that are defined without a -> m b you can just provide a value.

In above example, the field of DeityArgs could also be named using reserved identities (such as: type, where, etc), in order to avoid conflict, a prime symbol (') must be attached. For example, you can have:

data DeityArgs = DeityArgs
  { name      :: Text        -- Required Argument
  , mythology :: Maybe Text  -- Optional Argument
  , type'     :: Text
  } deriving (Generic)

The field name in the final request will be type instead of type'. The Morpheus request parser converts each of the reserved identities in Haskell 2010 to their corresponding names internally. This also applies to selections.

resolveDeity :: DeityArgs -> IORes e Deity
resolveDeity DeityArgs { name, mythology } = liftEither $ dbDeity name mythology

askDB :: Text -> Maybe Text -> IO (Either String Deity)
askDB = ...

To make this Query type available as an API, we define a GQLRootResolver and feed it to the Morpheus interpreter. A GQLRootResolver consists of query, mutation and subscription definitions, while we omit the latter for this example:

rootResolver :: GQLRootResolver IO () Query Undefined Undefined
rootResolver =
  GQLRootResolver
    { queryResolver = Query {deity = resolveDeity}
    , mutationResolver = Undefined
    , subscriptionResolver = Undefined
    }

gqlApi :: ByteString -> IO ByteString
gqlApi = interpreter rootResolver

As you can see, the API is defined as ByteString -> IO ByteString which we can either invoke directly or use inside an arbitrary web framework such as scotty or serverless-haskell. We'll go for scotty in this example:

main :: IO ()
main = scotty 3000 $ post "/api" $ raw =<< (liftIO . gqlApi =<< body)

If we now send a POST request to http://localhost:3000/api with a GraphQL Query as body for example in a tool like Insomnia:

query GetDeity {
  deity (name: "Morpheus") {
    fullName
    power
  }
}

our query will be resolved!

{
  "data": {
    "deity": {
      "fullName": "Morpheus",
      "power": "Shapeshifting"
    }
  }
}

Serverless Example

If you are interested in creating a Morpheus GraphQL API with Serverless, you should take a look at our example in this repository: Mythology API it is our example project build with Morpheus GraphQL and Serverless-Haskell, where you can query different mythology characters with GraphiQL.

Mythology API is deployed on : api.morpheusgraphql.com where you can test it with GraphiQL

Mythology Api

Advanced topics

Enums

You can use Union Types as Enums, but they're not allowed to have any parameters.

data City
  = Athens
  | Sparta
  | Corinth
  | Delphi
  | Argos
  deriving (Generic)

instance GQLType City where
  type KIND City = ENUM

Union types

To use union type, all you have to do is derive the GQLType class. Using GraphQL fragments, the arguments of each data constructor can be accessed from the GraphQL client.

data Character
  = CharacterDeity Deity -- Only <tyconName><conName> should generate direct link
  -- RECORDS
  | Creature { creatureName :: Text, creatureAge :: Int }
  --- Types
  | SomeDeity Deity
  | CharacterInt Int
  | SomeMutli Int Text
  --- ENUMS
  | Zeus
  | Cronus
  deriving (Generic, GQLType)

where Deity is an object.

As you see there are different kinds of unions. morpheus handles them all.

This type will be represented as

union Character =
    Deity # unwrapped union: because "Character" <> "Deity" == "CharacterDeity"
  | Creature
  | SomeDeity # wrapped union: because "Character" <> "Deity" /= SomeDeity
  | CharacterInt
  | SomeMutli
  | CharacterEnumObject # no-argument constructors all wrapped into an enum

type Creature {
  creatureName: String!
  creatureAge: Int!
}

type SomeDeity {
  _0: Deity!
}

type CharacterInt {
  _0: Int!
}

type SomeMutli {
  _0: Int!
  _1: String!
}

# enum
type CharacterEnumObject {
  enum: CharacterEnum!
}

enum CharacterEnum {
  Zeus
  Cronus
}

By default, union members will be generated with wrapper objects. There is one exception to this: if a constructor of a type is the type name concatinated with the name of the contained type, it will be referenced directly. That is, given:

data Song = { songName :: Text, songDuration :: Float } deriving (Generic, GQLType)

data Skit = { skitName :: Text, skitDuration :: Float } deriving (Generic, GQLType)

data WrappedNode
  = WrappedSong Song
  | WrappedSkit Skit
  deriving (Generic, GQLType)

data NonWrapped
  = NonWrappedSong Song
  | NonWrappedSkit Skit
  deriving (Generic, GQLType)

You will get the following schema:


# has wrapper types
union WrappedNode = WrappedSong | WrappedSkit

# is a direct union
union NonWrapped = Song | Skit

type WrappedSong {
  _0: Song!
}

type WrappedSKit {
  _0: Skit!
}

type Song {
  songDuration: Float!
  songName: String!
}

type Skit {
  skitDuration: Float!
  skitName: String!
}

Scalar types

To use custom scalar types, you need to provide implementations for parseValue and serialize respectively.

data Odd = Odd Int  deriving (Generic)

instance GQLScalar Odd where
  parseValue (Int x) = pure $ Odd (...  )
  parseValue (String x) = pure $ Odd (...  )
  serialize  (Odd value) = Int value

instance GQLType Odd where
  type KIND Odd = SCALAR

Applicative and Monad instance

The Resolver type has Applicative and Monad instances that can be used to compose resolvers.

Introspection

Morpheus converts your schema to a GraphQL introspection automatically. You can use tools like Insomnia to take a look at the introspection and validate your schema. If you need a description for your GQLType inside of the introspection you can define the GQLType instance manually and provide an implementation for the description function:

data Deity = Deity
{ ...
} deriving (Generic)

instance GQLType Deity where
  description = const "A supernatural being considered divine and sacred"

screenshots from Insomnia

alt text alt text alt text

Handling Errors

for errors you can use use either liftEither or failRes: at the and they have same result.

with liftEither

resolveDeity :: DeityArgs -> IORes e Deity
resolveDeity DeityArgs {} = liftEither $ dbDeity

dbDeity ::  IO Either Deity
dbDeity = pure $ Left "db error"

with failRes

resolveDeity :: DeityArgs -> IORes e Deity
resolveDeity DeityArgs { } = failRes "db error"

Mutations

In addition to queries, Morpheus also supports mutations. They behave just like regular queries and are defined similarly:

newtype Mutation m = Mutation
  { createDeity :: MutArgs -> m Deity
  } deriving (Generic, GQLType)

rootResolver :: GQLRootResolver IO  () Query Mutation Undefined
rootResolver =
  GQLRootResolver
    { queryResolver = Query {...}
    , mutationResolver = Mutation { createDeity }
    , subscriptionResolver = Undefined
    }
    where
      -- Mutation Without Event Triggering
      createDeity :: MutArgs -> ResolveM () IO Deity
      createDeity_args = lift setDBAddress

gqlApi :: ByteString -> IO ByteString
gqlApi = interpreter rootResolver

Subscriptions

In morpheus subscription and mutation communicate with Events, Event consists with user defined Channel and Content.

Every subscription has its own Channel by which it will be triggered

data Channel
  = ChannelA
  | ChannelB

data Content
  = ContentA Int
  | ContentB Text

type MyEvent = Event Channel Content

newtype Query m = Query
  { deity :: m Deity
  } deriving (Generic)

newtype Mutation m = Mutation
  { createDeity :: m Deity
  } deriving (Generic)

newtype Subscription (m ::  * -> * ) = Subscription
  { newDeity :: m  Deity
  } deriving (Generic)

type APIEvent = Event Channel Content

rootResolver :: GQLRootResolver IO APIEvent Query Mutation Subscription
rootResolver = GQLRootResolver
  { queryResolver        = Query { deity = fetchDeity }
  , mutationResolver     = Mutation { createDeity }
  , subscriptionResolver = Subscription { newDeity }
  }
 where
  -- Mutation Without Event Triggering
  createDeity :: ResolveM EVENT IO Address
  createDeity = do
      requireAuthorized
      publish [Event { channels = [ChannelA], content = ContentA 1 }]
      lift dbCreateDeity
  newDeity = subscribe [ChannelA] $ do
      requireAuthorized
      lift deityByEvent
   where
    deityByEvent (Event [ChannelA] (ContentA _value)) = fetchDeity  -- resolve New State
    deityByEvent (Event [ChannelA] (ContentB _value)) = fetchDeity   -- resolve New State
    deityByEvent _ = fetchDeity -- Resolve Old State

Morpheus GraphQL Client with Template haskell QuasiQuotes

defineByDocumentFile
    "./schema.gql"
  [gql|
    query GetHero ($character: Character)
      {
        deity (fatherOf:$character) {
          name
          power
          worships {
            deity2Name: name
          }
        }
      }
  |]

with schema:

input Character {
  name: String!
}

type Deity {
  name: String!
  worships: Deity
  power: Power!
}

enum Power {
  Lightning
  Teleportation
  Omniscience
}

will validate query and Generate:

data GetHero = GetHero {
  deity: DeityDeity
}

-- from: {user
data DeityDeity = DeityDeity {
  name: Text,
  worships: Maybe DeityWorshipsDeity
  power: Power
}

-- from: {deity{worships
data DeityWorshipsDeity = DeityWorshipsDeity {
  name: Text,
}

data Power =
    PowerLightning
  | PowerTeleportation
  | PowerOmniscience

data GetHeroArgs = GetHeroArgs {
  getHeroArgsCharacter: Character
}

data Character = Character {
  characterName: Person
}

as you see, response type field name collision can be handled with GraphQL alias.

with fetch you can fetch well typed response GetHero.

  fetchHero :: Args GetHero -> m (Either String GetHero)
  fetchHero = fetch jsonRes args
      where
        args = GetHeroArgs {getHeroArgsCharacter = Person {characterName = "Zeus"}}
        jsonRes :: ByteString -> m ByteString
        jsonRes = <GraphQL APi>

in this case, jsonRes resolves a request into a response in some monad m.

A fetch resolver implementation against a real API may look like the following:

{-# LANGUAGE OverloadedStrings #-}

import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Char8 as C8
import Network.HTTP.Req

resolver :: String -> ByteString -> IO ByteString
resolver tok b = runReq defaultHttpConfig $ do
    let headers = header "Content-Type" "application/json"
    responseBody <$> req POST (https "swapi.graph.cool") (ReqBodyLbs b) lbsResponse headers

this is demonstrated in examples/src/Client/StarWarsClient.hs

types can be generated from introspection too:

defineByIntrospectionFile "./introspection.json"

Morpheus CLI for Code Generating

you should use morpheus-graphql-cli

Showcase

Below are the list of projects using Morpheus GraphQL. If you want to start using Morpheus GraphQL, they are good templates to begin with.

Edit this section and send PR if you want to share your project.

About

The name

Morpheus is the greek god of sleep and dreams whose name comes from the greek word μορφή meaning form or shape. He is said to be able to mimic different forms and GraphQL is good at doing exactly that: Transforming data in the shape of many different APIs.

Team

Morpheus is written and maintained by nalchevanidze

Roadmap