{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

{-|
Module      :  Data.GraphQL.Query
Maintainer  :  Brandon Chinn <brandonchinn178@gmail.com>
Stability   :  experimental
Portability :  portable

Definitions needed by GraphQL queries.
-}
module Data.GraphQL.Query (
  GraphQLQuery (..),
  query,
) where

import Data.Aeson (Value)
import Data.Aeson.Schema (IsSchema, Schema)
import Data.Text (Text)
import qualified Data.Text as Text
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax (lift)

-- | A type class for defining GraphQL queries.
--
--  Should be generated via the `graphql-codegen` command. Any manual instances needs
--  to be certain that `getArgs query` satisfies the arguments defined in
--  `getQueryText query`, and that the result adheres to `ResultSchema query`.
class (IsSchema (ResultSchema query)) => GraphQLQuery query where
  type ResultSchema query :: Schema
  getQueryName :: query -> Text
  getQueryText :: query -> Text
  getArgs :: query -> Value

-- | A quasiquoter that interpolates the given string as raw text.
--
--  Trying to avoid a dependency on raw-strings-qq
query :: QuasiQuoter
query :: QuasiQuoter
query =
  QuasiQuoter
    { quoteExp :: String -> Q Exp
quoteExp = Text -> Q Exp
forall {m :: * -> *}. Quote m => Text -> m Exp
liftText (Text -> Q Exp) -> (String -> Text) -> String -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.strip (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
    , quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"Cannot use the 'query' QuasiQuoter for patterns"
    , quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"Cannot use the 'query' QuasiQuoter for types"
    , quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"Cannot use the 'query' QuasiQuoter for declarations"
    }
  where
    liftText :: Text -> m Exp
liftText Text
s = [|Text.pack $(String -> m Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => String -> m Exp
lift (String -> m Exp) -> String -> m Exp
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
s)|]