>
> module Language.SQL.SimpleSQL.Errors
> (ParseError(..)
>
> ,convParseError
> ) where
> import Text.Parsec (sourceColumn,sourceLine,sourceName,errorPos)
> import qualified Text.Parsec as P (ParseError)
>
> data ParseError = ParseError
> {peErrorString :: String
>
> ,peFilename :: FilePath
>
> ,pePosition :: (Int,Int)
>
> ,peFormattedError :: String
>
>
> } deriving (Eq,Show)
> convParseError :: String -> P.ParseError -> ParseError
> convParseError src e =
> ParseError
> {peErrorString = show e
> ,peFilename = sourceName p
> ,pePosition = (sourceLine p, sourceColumn p)
> ,peFormattedError = formatError src e}
> where
> p = errorPos e
format the error more nicely: emacs format for positioning, plus
context
> formatError :: String -> P.ParseError -> String
> formatError src e =
> sourceName p ++ ":" ++ show (sourceLine p)
> ++ ":" ++ show (sourceColumn p) ++ ":"
> ++ context
> ++ show e
> where
> context =
> let lns = take 1 $ drop (sourceLine p - 1) $ lines src
> in case lns of
> [x] -> "\n" ++ x ++ "\n"
> ++ replicate (sourceColumn p - 1) ' ' ++ "^\n"
> _ -> ""
> p = errorPos e