Re: Status of the rich errors proposal

2019-10-29 Thread Alp Mestanogullari

Hello Javier,

Ben and I have indeed been thinking about how to improve the situation, 
and have been talking to a few fellow Haskellers in the tooling/IDE 
space to get a first round of feedback on the ideas that we came up 
with. I will soon be writing down a proposal for one of those ideas, 
that is likely to work well for everyone (GHC devs, tooling authors and 
more generally GHC API consumers).


Once that document is ready and up on github, I wil make sure to send 
the link here on ghc-devs@.


On 23/10/2019 08:52, Javier Neira Sanchez wrote:
Hi, lately i am being collaborated in the haskell-ide-engine (hie) 
repo and one of the issues i get to fix was related with the parsing 
of ghc errors.
It turns out that delimiters of terms in errors are different in 
windows (`term') and *nix (‘term’) systems and that drive to parse errors.
Quite code actions and diagnostics are based in parsing them and they 
were broken in windows.
I am afraid that the code is very brittle and close to human readable 
error messages. the actual code look like this:


-- | Extract a term from a compiler message.
-- It looks for terms delimited between '‘' and '’' falling back to 
'`' and '\''

-- (the used ones in Windows systems).
extractTerm :: T.Text -> T.Text
extractTerm txt =
  case extract '‘' '’' txt of
    ""  -> extract '`' '\'' txt -- Needed for windows
    term -> term
  where extract b e = T.dropWhile (== b)
    . T.dropWhileEnd (== e)
    . T.dropAround (\c -> c /= b && c /= e)
or

extractImportableTerm :: T.Text -> Maybe (T.Text, SymbolImport SymbolType)
extractImportableTerm dirtyMsg = do
  (n, s) <- extractedTerm
  let n' = T.strip n
  return (n', s)
  where
    importMsg = S.headMay
  -- Get rid of the rename suggestion parts
  $ T.splitOn "Perhaps you meant "
  $ T.replace "\n" " "
  -- Get rid of trailing/leading whitespace on each individual line
  $ T.unlines
  $ map T.strip
  $ T.lines
  $ T.replace "* " "" -- Needed for Windows
  $ T.replace "• " "" dirtyMsg
    extractTerm prefix symTy =
  importMsg
  >>= T.stripPrefix prefix
  >>= \name -> Just (name, Import symTy)
    extractType b =
  extractTerm ("Not in scope: type constructor or class " <> b) Type
    extractedTerm = asum
  [ extractTerm "Variable not in scope: " Symbol
  , extractType "‘"
  , extractType "`" -- Needed for windows
  , extractTerm "Data constructor not in scope: " Constructor]

It is clearly unsatisfactory but hard to improve without changing the 
messages to make it more structured.
Moreover any legitimate change on errors to make it better will likely 
break it.


After exposing my worries in the hie irc channel, @mpickering pointed 
out that it is already a proposal to improve error messages:


https://github.com/bgamari/ghc-proposals/blob/rich-errors-proposal/proposals/-rich-errors-proposal.rst

that nicely will improve the state of things.

Otoh there are already a way to output ghc errors as json (see 
https://gitlab.haskell.org/ghc/ghc/issues/13190). It contains valuable 
info about the error in specific fields but the message itself is in 
plain text.
So merging both features will let tools to handle compiler errors 
without use the ghc api directly if needed.


what is the status of the proposal? hie an other tooling developers 
will welcome it very heartly.


Thanks in advance!

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


--
Alp Mestanogullari, Haskell Consultant
Well-Typed LLP, https://www.well-typed.com/

Registered in England and Wales, OC335890
118 Wymering Mansions, Wymering Road, London, W9 2NF, England

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Status of the rich errors proposal

2019-10-28 Thread Richard Eisenberg
Ben Gamari is, I believe, leading the effort with that proposal. It continues 
to get attention but has not yet blossomed to something we're ready to debate 
widely. This is a hard nut to crack, and we'd like to get it right. So I guess 
all there is to say right now is that the effort is ongoing, but we don't have 
anything concrete to report at the moment.

Richard

> On Oct 23, 2019, at 7:52 AM, Javier Neira Sanchez  
> wrote:
> 
> Hi, lately i am being collaborated in the haskell-ide-engine (hie) repo and 
> one of the issues i get to fix was related with the parsing of ghc errors.
> It turns out that delimiters of terms in errors are different in windows 
> (`term') and *nix (‘term’) systems and that drive to parse errors.
> Quite code actions and diagnostics are based in parsing them and they were 
> broken in windows.
> I am afraid that the code is very brittle and close to human readable error 
> messages. the actual code look like this:
> 
> -- | Extract a term from a compiler message.
> -- It looks for terms delimited between '‘' and '’' falling back to '`' and 
> '\''
> -- (the used ones in Windows systems).
> extractTerm :: T.Text -> T.Text
> extractTerm txt =
>   case extract '‘' '’' txt of
> ""  -> extract '`' '\'' txt -- Needed for windows
> term -> term
>   where extract b e = T.dropWhile (== b)
> . T.dropWhileEnd (== e)
> . T.dropAround (\c -> c /= b && c /= e)
> 
> 
> or
> 
> extractImportableTerm :: T.Text -> Maybe (T.Text, SymbolImport SymbolType)
> extractImportableTerm dirtyMsg = do
>   (n, s) <- extractedTerm
>   let n' = T.strip n
>   return (n', s)
>   where
> importMsg = S.headMay
>   -- Get rid of the rename suggestion parts
>   $ T.splitOn "Perhaps you meant "
>   $ T.replace "\n" " "
>   -- Get rid of trailing/leading whitespace on each individual line
>   $ T.unlines
>   $ map T.strip
>   $ T.lines
>   $ T.replace "* " "" -- Needed for Windows
>   $ T.replace "• " "" dirtyMsg
> extractTerm prefix symTy =
>   importMsg
>   >>= T.stripPrefix prefix
>   >>= \name -> Just (name, Import symTy)
> extractType b =
>   extractTerm ("Not in scope: type constructor or class " <> b) Type
> extractedTerm = asum
>   [ extractTerm "Variable not in scope: " Symbol
>   , extractType "‘"
>   , extractType "`" -- Needed for windows
>   , extractTerm "Data constructor not in scope: " Constructor]
> 
> It is clearly unsatisfactory but hard to improve without changing the 
> messages to make it more structured.
> Moreover any legitimate change on errors to make it better will likely break 
> it.
> 
> After exposing my worries in the hie irc channel, @mpickering pointed out 
> that it is already a proposal to improve error messages:
> 
> https://github.com/bgamari/ghc-proposals/blob/rich-errors-proposal/proposals/-rich-errors-proposal.rst
>  
> 
> 
> that nicely will improve the state of things.
> 
> Otoh there are already a way to output ghc errors as json (see 
> https://gitlab.haskell.org/ghc/ghc/issues/13190 
> ). It contains valuable info 
> about the error in specific fields but the message itself is in plain text.
> So merging both features will let tools to handle compiler errors without use 
> the ghc api directly if needed.
> 
> what is the status of the proposal? hie an other tooling developers will 
> welcome it very heartly.
> 
> Thanks in advance!
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Status of the rich errors proposal

2019-10-22 Thread Javier Neira Sanchez
Hi, lately i am being collaborated in the haskell-ide-engine (hie) repo and
one of the issues i get to fix was related with the parsing of ghc errors.
It turns out that delimiters of terms in errors are different in windows
(`term') and *nix (‘term’) systems and that drive to parse errors.
Quite code actions and diagnostics are based in parsing them and they were
broken in windows.
I am afraid that the code is very brittle and close to human readable error
messages. the actual code look like this:

-- | Extract a term from a compiler message.

-- It looks for terms delimited between '‘' and '’' falling back to '`' and '\''

-- (the used ones in Windows systems).

extractTerm :: T.Text -> T.Text

extractTerm txt =

  case extract '‘' '’' txt of

""  -> extract '`' '\'' txt -- Needed for windows

term -> term

  where extract b e = T.dropWhile (== b)

. T.dropWhileEnd (== e)

. T.dropAround (\c -> c /= b && c /= e)


or

extractImportableTerm :: T.Text -> Maybe (T.Text, SymbolImport SymbolType)

extractImportableTerm dirtyMsg = do

  (n, s) <- extractedTerm

  let n' = T.strip n

  return (n', s)

  where

importMsg = S.headMay

  -- Get rid of the rename suggestion parts

  $ T.splitOn "Perhaps you meant "

  $ T.replace "\n" " "

  -- Get rid of trailing/leading whitespace on each individual line

  $ T.unlines

  $ map T.strip

  $ T.lines

  $ T.replace "* " "" -- Needed for Windows

  $ T.replace "• " "" dirtyMsg

extractTerm prefix symTy =

  importMsg

  >>= T.stripPrefix prefix

  >>= \name -> Just (name, Import symTy)

extractType b =

  extractTerm ("Not in scope: type constructor or class " <> b) Type

extractedTerm = asum

  [ extractTerm "Variable not in scope: " Symbol

  , extractType "‘"

  , extractType "`" -- Needed for windows

  , extractTerm "Data constructor not in scope: " Constructor]


It is clearly unsatisfactory but hard to improve without changing the
messages to make it more structured.
Moreover any legitimate change on errors to make it better will likely
break it.

After exposing my worries in the hie irc channel, @mpickering pointed out
that it is already a proposal to improve error messages:

https://github.com/bgamari/ghc-proposals/blob/rich-errors-proposal/proposals/-rich-errors-proposal.rst

that nicely will improve the state of things.

Otoh there are already a way to output ghc errors as json (see
https://gitlab.haskell.org/ghc/ghc/issues/13190). It contains valuable info
about the error in specific fields but the message itself is in plain text.
So merging both features will let tools to handle compiler errors without
use the ghc api directly if needed.

what is the status of the proposal? hie an other tooling developers will
welcome it very heartly.

Thanks in advance!
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs