megaparsec/Text/Megaparsec/Error.hs

182 lines
5.9 KiB
Haskell
Raw Normal View History

2008-01-13 20:53:15 +03:00
-- |
-- Module : Text.Megaparsec.Error
-- Copyright : © 2015 Megaparsec contributors
-- © 2007 Paolo Martini
-- © 19992001 Daan Leijen
2015-07-28 16:32:19 +03:00
-- License : BSD3
--
-- Maintainer : Mark Karpov <markkarpov@opmbx.org>
2015-07-29 11:38:32 +03:00
-- Stability : experimental
2008-01-13 20:53:15 +03:00
-- Portability : portable
2015-07-28 16:32:19 +03:00
--
-- Parse errors.
2008-01-13 20:53:15 +03:00
module Text.Megaparsec.Error
2015-08-12 20:51:06 +03:00
( Message (..)
, messageString
, badMessage
, ParseError
, errorPos
, errorMessages
, errorIsUnknown
, newErrorMessage
, newErrorUnknown
, addErrorMessage
, setErrorMessage
, setErrorPos
, mergeError
, showMessages )
2015-07-28 16:32:19 +03:00
where
2008-01-13 20:53:15 +03:00
import Data.Bool (bool)
import Data.List (intercalate)
import Data.Maybe (fromMaybe)
2008-01-13 20:53:15 +03:00
import Text.Megaparsec.Pos
2008-01-13 20:53:15 +03:00
-- | This data type represents parse error messages. There are three kinds
-- of messages:
--
2015-08-12 15:41:22 +03:00
-- > data Message = Unexpected String
-- > | Expected String
-- > | Message String
2015-07-28 16:32:19 +03:00
--
2015-07-29 11:38:32 +03:00
-- The fine distinction between different kinds of parse errors allows the
-- system to generate quite good error messages for the user.
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
data Message
= Unexpected !String
| Expected !String
| Message !String
deriving (Show, Eq)
2008-01-13 20:53:15 +03:00
instance Enum Message where
2015-08-12 20:51:06 +03:00
fromEnum (Unexpected _) = 0
fromEnum (Expected _) = 1
fromEnum (Message _) = 2
toEnum _ = error "Text.Megaparsec.Error: toEnum is undefined for Message"
2008-01-13 20:53:15 +03:00
instance Ord Message where
2015-08-12 20:51:06 +03:00
compare m1 m2 =
case compare (fromEnum m1) (fromEnum m2) of
LT -> LT
EQ -> compare (messageString m1) (messageString m2)
GT -> GT
2008-01-13 20:53:15 +03:00
2015-08-12 15:41:22 +03:00
-- | Extract the message string from an error message.
2008-01-13 20:53:15 +03:00
messageString :: Message -> String
messageString (Unexpected s) = s
messageString (Expected s) = s
messageString (Message s) = s
-- | Test if message string is empty.
badMessage :: Message -> Bool
badMessage = null . messageString
2008-01-13 20:53:15 +03:00
-- | The data type @ParseError@ represents parse errors. It provides the
-- source position ('SourcePos') of the error and a list of error messages
-- ('Message'). A @ParseError@ can be returned by the function
-- 'Text.Parsec.Prim.parse'. @ParseError@ is an instance of the 'Show' and
-- 'Eq' type classes.
2008-01-13 20:53:15 +03:00
data ParseError = ParseError
2015-08-12 20:51:06 +03:00
{ -- | Extract the source position from @ParseError@.
errorPos :: !SourcePos
-- | Extract the list of error messages from @ParseError@.
, errorMessages :: [Message] }
deriving Eq
2008-01-13 20:53:15 +03:00
2015-07-29 11:38:32 +03:00
instance Show ParseError where
2015-08-12 20:51:06 +03:00
show e = show (errorPos e) ++ ":\n" ++ showMessages (errorMessages e)
2015-07-29 11:38:32 +03:00
2015-07-30 21:36:54 +03:00
-- | Test whether given @ParseError@ has associated collection of error
-- messages. Return @True@ if it has none and @False@ otherwise.
2008-01-13 20:53:15 +03:00
errorIsUnknown :: ParseError -> Bool
2015-07-29 11:38:32 +03:00
errorIsUnknown (ParseError _ ms) = null ms
2008-01-13 20:53:15 +03:00
2015-07-29 11:38:32 +03:00
-- Creation of parse errors
2008-01-13 20:53:15 +03:00
2015-07-30 21:36:54 +03:00
-- | @newErrorUnknown pos@ creates @ParseError@ without any associated
-- message but with specified position @pos@.
2008-01-13 20:53:15 +03:00
newErrorUnknown :: SourcePos -> ParseError
2015-07-29 11:38:32 +03:00
newErrorUnknown pos = ParseError pos []
2008-01-13 20:53:15 +03:00
2015-07-30 21:36:54 +03:00
-- | @newErrorMessage m pos@ creates @ParseError@ with message @m@ and
-- associated position @pos@. If message @m@ has empty message string, it
-- won't be included.
2015-07-30 21:36:54 +03:00
2008-01-13 20:53:15 +03:00
newErrorMessage :: Message -> SourcePos -> ParseError
newErrorMessage m pos = ParseError pos $ bool [m] [] (badMessage m)
2008-01-13 20:53:15 +03:00
2015-07-30 21:36:54 +03:00
-- | @addErrorMessage m err@ returns @ParseError@ @err@ with message @m@
-- added. This function makes sure that list of messages is always sorted
-- and doesn't contain duplicates or messages with empty message strings.
2015-07-30 21:36:54 +03:00
2008-01-13 20:53:15 +03:00
addErrorMessage :: Message -> ParseError -> ParseError
addErrorMessage m (ParseError pos ms) =
2015-08-12 20:51:06 +03:00
ParseError pos $ bool (pre ++ [m] ++ post) ms (badMessage m)
where pre = filter (< m) ms
post = filter (> m) ms
2008-01-13 20:53:15 +03:00
-- | @setErrorMessage m err@ returns @err@ with message @m@ added. This
-- function also deletes all existing error messages that were created with
-- the same constructor as @m@. If message @m@ has empty message string, the
-- function just returns the original @err@.
setErrorMessage :: Message -> ParseError -> ParseError
setErrorMessage m e@(ParseError pos ms) =
2015-08-12 20:51:06 +03:00
bool (addErrorMessage m $ ParseError pos xs) e (badMessage m)
where xs = filter ((/= fromEnum m) . fromEnum) ms
2015-07-30 21:36:54 +03:00
-- | @setErrorPos pos err@ returns @ParseError@ identical to @err@, but with
-- position @pos@.
2008-01-13 20:53:15 +03:00
setErrorPos :: SourcePos -> ParseError -> ParseError
2015-07-29 11:38:32 +03:00
setErrorPos pos (ParseError _ ms) = ParseError pos ms
2008-01-13 20:53:15 +03:00
2015-07-30 21:36:54 +03:00
-- | Merge two error data structures into one joining their collections of
-- messages and preferring longest match. In other words earlier error
-- message is discarded. This may seem counter-intuitive, but @mergeError@
-- is only used to merge error messages of alternative branches of parsing
-- and in this case longest match should be preferred.
2015-07-30 21:36:54 +03:00
2008-01-13 20:53:15 +03:00
mergeError :: ParseError -> ParseError -> ParseError
mergeError e1@(ParseError pos1 _) e2@(ParseError pos2 ms2) =
2015-08-12 20:51:06 +03:00
case pos1 `compare` pos2 of
LT -> e2
EQ -> foldr addErrorMessage e1 ms2
GT -> e1
-- | @showMessages ms@ transforms list of error messages @ms@ into
2015-07-30 21:36:54 +03:00
-- their textual representation.
showMessages :: [Message] -> String
showMessages [] = "unknown parse error"
showMessages ms = tail $ foldMap (fromMaybe "") (zipWith f ns rs)
2015-08-12 20:51:06 +03:00
where (unexpected, ms') = span ((== 0) . fromEnum) ms
(expected, messages) = span ((== 1) . fromEnum) ms'
f prefix m = (prefix ++) <$> m
ns = ["\nunexpected ","\nexpecting ","\n"]
rs = renderMsgs <$> [unexpected, expected, messages]
-- | Render collection of messages. If the collection is empty, return
-- 'Nothing', else return textual representation of the messages inside
-- 'Just'.
renderMsgs :: [Message] -> Maybe String
renderMsgs [] = Nothing
renderMsgs ms = Just . orList $ messageString <$> ms
-- | Print a pretty list where items are separated with commas and the word
-- “or” according to rules of English punctuation.
orList :: [String] -> String
orList [] = ""
orList [x] = x
orList [x,y] = x ++ " or " ++ y
orList xs = intercalate ", " (init xs) ++ ", or " ++ last xs