graphql/tests/Language/GraphQL/ErrorSpec.hs
Eugen Wissner 1af95345d2 Deprecate internal error generation functions
The functions generating errors in the executor should be changed anyway
when we provide better error messages from the executor, with the error
location and response path. So public definitions of these functions are
deprecated now and they are replaced by more generic functions in the
executor code.
2021-05-10 09:43:39 +02:00

37 lines
1.2 KiB
Haskell

{- This Source Code Form is subject to the terms of the Mozilla Public License,
v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.ErrorSpec
( spec
) where
import qualified Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty (..))
import Language.GraphQL.Error
import Test.Hspec
( Spec
, describe
, it
, shouldBe
)
import Text.Megaparsec (PosState(..))
import Text.Megaparsec.Error (ParseError(..), ParseErrorBundle(..))
import Text.Megaparsec.Pos (SourcePos(..), mkPos)
spec :: Spec
spec = describe "parseError" $
it "generates response with a single error" $ do
let parseErrors = TrivialError 0 Nothing mempty :| []
posState = PosState
{ pstateInput = ""
, pstateOffset = 0
, pstateSourcePos = SourcePos "" (mkPos 1) (mkPos 1)
, pstateTabWidth = mkPos 1
, pstateLinePrefix = ""
}
Response Aeson.Null actual <-
parseError (ParseErrorBundle parseErrors posState)
length actual `shouldBe` 1