{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RecordWildCards #-}
module Language.GraphQL.Error
    ( Error(..)
    , Path(..)
    , ResolverException(..)
    , Response(..)
    , ResponseEventStream
    , parseError
    ) where
import Conduit
import Control.Exception (Exception(..))
import Data.Sequence (Seq(..), (|>))
import qualified Data.Sequence as Seq
import Data.Text (Text)
import qualified Data.Text as Text
import Language.GraphQL.AST (Location(..))
import Language.GraphQL.Execute.Coerce
import Prelude hiding (null)
import Text.Megaparsec
    ( ParseErrorBundle(..)
    , PosState(..)
    , SourcePos(..)
    , errorOffset
    , parseErrorTextPretty
    , reachOffset
    , unPos
    )
parseError :: (Applicative f, Serialize a)
    => ParseErrorBundle Text Void
    -> f (Response a)
parseError :: forall (f :: * -> *) a.
(Applicative f, Serialize a) =>
ParseErrorBundle Text Void -> f (Response a)
parseError ParseErrorBundle{NonEmpty (ParseError Text Void)
PosState Text
bundleErrors :: NonEmpty (ParseError Text Void)
bundlePosState :: PosState Text
bundleErrors :: forall s e. ParseErrorBundle s e -> NonEmpty (ParseError s e)
bundlePosState :: forall s e. ParseErrorBundle s e -> PosState s
..}  =
    Response a -> f (Response a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Response a -> f (Response a)) -> Response a -> f (Response a)
forall a b. (a -> b) -> a -> b
$ a -> Seq Error -> Response a
forall a. a -> Seq Error -> Response a
Response a
forall a. Serialize a => a
null (Seq Error -> Response a) -> Seq Error -> Response a
forall a b. (a -> b) -> a -> b
$ (Seq Error, PosState Text) -> Seq Error
forall a b. (a, b) -> a
fst
        ((Seq Error, PosState Text) -> Seq Error)
-> (Seq Error, PosState Text) -> Seq Error
forall a b. (a -> b) -> a -> b
$ ((Seq Error, PosState Text)
 -> ParseError Text Void -> (Seq Error, PosState Text))
-> (Seq Error, PosState Text)
-> NonEmpty (ParseError Text Void)
-> (Seq Error, PosState Text)
forall b a. (b -> a -> b) -> b -> NonEmpty a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (Seq Error, PosState Text)
-> ParseError Text Void -> (Seq Error, PosState Text)
forall {s} {e} {s}.
(VisualStream s, ShowErrorComponent e, TraversableStream s) =>
(Seq Error, PosState s)
-> ParseError s e -> (Seq Error, PosState s)
go (Seq Error
forall a. Seq a
Seq.empty, PosState Text
bundlePosState) NonEmpty (ParseError Text Void)
bundleErrors
  where
    errorObject :: ParseError s e -> SourcePos -> Error
errorObject ParseError s e
s SourcePos{FilePath
Pos
sourceName :: FilePath
sourceLine :: Pos
sourceColumn :: Pos
sourceName :: SourcePos -> FilePath
sourceLine :: SourcePos -> Pos
sourceColumn :: SourcePos -> Pos
..} = Error
        { $sel:message:Error :: Text
message = FilePath -> Text
Text.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
forall a. HasCallStack => [a] -> [a]
init (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ ParseError s e -> FilePath
forall s e.
(VisualStream s, ShowErrorComponent e) =>
ParseError s e -> FilePath
parseErrorTextPretty ParseError s e
s
        , $sel:locations:Error :: [Location]
locations = [Word -> Word -> Location
Location (Pos -> Word
unPos' Pos
sourceLine) (Pos -> Word
unPos' Pos
sourceColumn)]
        , $sel:path:Error :: [Path]
path = []
        }
    unPos' :: Pos -> Word
unPos' = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word) -> (Pos -> Int) -> Pos -> Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pos -> Int
unPos
    go :: (Seq Error, PosState s)
-> ParseError s e -> (Seq Error, PosState s)
go (Seq Error
result, PosState s
state) ParseError s e
x =
        let (Maybe FilePath
_, PosState s
newState) = Int -> PosState s -> (Maybe FilePath, PosState s)
forall s.
TraversableStream s =>
Int -> PosState s -> (Maybe FilePath, PosState s)
reachOffset (ParseError s e -> Int
forall s e. ParseError s e -> Int
errorOffset ParseError s e
x) PosState s
state
            sourcePosition :: SourcePos
sourcePosition = PosState s -> SourcePos
forall s. PosState s -> SourcePos
pstateSourcePos PosState s
newState
         in (Seq Error
result Seq Error -> Error -> Seq Error
forall a. Seq a -> a -> Seq a
|> ParseError s e -> SourcePos -> Error
forall {s} {e}.
(VisualStream s, ShowErrorComponent e) =>
ParseError s e -> SourcePos -> Error
errorObject ParseError s e
x SourcePos
sourcePosition, PosState s
newState)
data Path
    = Segment Text 
    | Index Int 
    deriving (Path -> Path -> Bool
(Path -> Path -> Bool) -> (Path -> Path -> Bool) -> Eq Path
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
/= :: Path -> Path -> Bool
Eq, Int -> Path -> FilePath -> FilePath
[Path] -> FilePath -> FilePath
Path -> FilePath
(Int -> Path -> FilePath -> FilePath)
-> (Path -> FilePath)
-> ([Path] -> FilePath -> FilePath)
-> Show Path
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: Int -> Path -> FilePath -> FilePath
showsPrec :: Int -> Path -> FilePath -> FilePath
$cshow :: Path -> FilePath
show :: Path -> FilePath
$cshowList :: [Path] -> FilePath -> FilePath
showList :: [Path] -> FilePath -> FilePath
Show)
data Error = Error
    { Error -> Text
message :: Text
    , Error -> [Location]
locations :: [Location]
    , Error -> [Path]
path :: [Path]
    } deriving (Error -> Error -> Bool
(Error -> Error -> Bool) -> (Error -> Error -> Bool) -> Eq Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Error -> Error -> Bool
== :: Error -> Error -> Bool
$c/= :: Error -> Error -> Bool
/= :: Error -> Error -> Bool
Eq, Int -> Error -> FilePath -> FilePath
[Error] -> FilePath -> FilePath
Error -> FilePath
(Int -> Error -> FilePath -> FilePath)
-> (Error -> FilePath)
-> ([Error] -> FilePath -> FilePath)
-> Show Error
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: Int -> Error -> FilePath -> FilePath
showsPrec :: Int -> Error -> FilePath -> FilePath
$cshow :: Error -> FilePath
show :: Error -> FilePath
$cshowList :: [Error] -> FilePath -> FilePath
showList :: [Error] -> FilePath -> FilePath
Show)
data Response a = Response
    { forall a. Response a -> a
data' :: a
    , forall a. Response a -> Seq Error
errors :: Seq Error
    } deriving (Response a -> Response a -> Bool
(Response a -> Response a -> Bool)
-> (Response a -> Response a -> Bool) -> Eq (Response a)
forall a. Eq a => Response a -> Response a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Response a -> Response a -> Bool
== :: Response a -> Response a -> Bool
$c/= :: forall a. Eq a => Response a -> Response a -> Bool
/= :: Response a -> Response a -> Bool
Eq, Int -> Response a -> FilePath -> FilePath
[Response a] -> FilePath -> FilePath
Response a -> FilePath
(Int -> Response a -> FilePath -> FilePath)
-> (Response a -> FilePath)
-> ([Response a] -> FilePath -> FilePath)
-> Show (Response a)
forall a. Show a => Int -> Response a -> FilePath -> FilePath
forall a. Show a => [Response a] -> FilePath -> FilePath
forall a. Show a => Response a -> FilePath
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Response a -> FilePath -> FilePath
showsPrec :: Int -> Response a -> FilePath -> FilePath
$cshow :: forall a. Show a => Response a -> FilePath
show :: Response a -> FilePath
$cshowList :: forall a. Show a => [Response a] -> FilePath -> FilePath
showList :: [Response a] -> FilePath -> FilePath
Show)
type ResponseEventStream m a = ConduitT () (Response a) m ()
data ResolverException = forall e. Exception e => ResolverException e
instance Show ResolverException where
    show :: ResolverException -> FilePath
show (ResolverException e
e) = e -> FilePath
forall a. Show a => a -> FilePath
show e
e
instance Exception ResolverException