haskell / error-messages

73 stars 18 forks source link

Better suggestion for ambiguous type variables in certain situations #7

Open noughtmare opened 3 years ago

noughtmare commented 3 years ago

In this recent stackoverflow question the asker presents the following piece of code (I have slightly adapted it) which gives an unhelpful error message:

module Test where

import Data.Aeson
import Data.Text (Text, unpack, pack)
import Text.Ginger
import Data.Functor.Identity
import Data.Function

mapLeft f (Left x) = Left (f x)
mapLeft _ (Right x) = Right x

tshow = pack . show

renderTemplate :: ToJSON c => Text -> c -> Either Text Text
renderTemplate template ctx = do
  tpl <- tplEither
  let ctxGVal = rawJSONToGVal $ toJSON ctx
  let r = easyRender ctxGVal tpl
  return r
  where
    tplEither :: Either Text (Template SourcePos)
    tplEither = parseGinger nullResolver Nothing (unpack template) & runIdentity & mapLeft tshow
    nullResolver :: IncludeResolver Identity
    nullResolver = const $ return Nothing

The error message is:

Ginger.hs:18:11: error:
    • Could not deduce (ToGVal
                          (Run SourcePos (Control.Monad.Trans.Writer.Lazy.Writer Text) Text)
                          (GVal m0))
        arising from a use of ‘easyRender’
      from the context: ToJSON c
        bound by the type signature for:
                   renderTemplate :: forall c.
                                     ToJSON c =>
                                     Text -> c -> Either Text Text
        at Ginger.hs:14:1-59
      The type variable ‘m0’ is ambiguous
      These potential instance exist:
        instance ToGVal m (GVal m) -- Defined in ‘Text.Ginger.GVal’
    • In the expression: easyRender ctxGVal tpl
      In an equation for ‘r’: r = easyRender ctxGVal tpl
      In the expression:
        do tpl <- tplEither
           let ctxGVal = rawJSONToGVal $ toJSON ctx
           let r = easyRender ctxGVal tpl
           return r
   |
18 |   let r = easyRender ctxGVal tpl
   |           ^^^^^^^^^^^^^^^^^^^^^^

It is large but it is fairly clear what the issue is: m0 is ambiguous. There is even a potential instance listed, but that is not really actionable unless the programmer understands that the m in that instance needs to be Run SourcePos (Control.Monad.Trans.Writer.Lazy.Writer Text) Text which can be hard to see for less experienced programmers.

In such ambiguous cases where there is only one potential instance then it might make sense to give a more elaborate explanation about how that instance could be used. In this case it could be:

These potential instance exist:
        instance ToGVal m (GVal m) -- Defined in ‘Text.Ginger.GVal’
To use this instance you can add a type signature to `ctxGVal`:
        ctxGVal :: GVal (Run SourcePos (Control.Monad.Trans.Writer.Lazy.Writer Text) Text)

Or perhaps it is easier (for GHC) to suggest TypeApplications:

To use this instance you can use `TypeApplications`:
        easyRender @_ @_ @(GVal (Run SourcePos (Control.Monad.Trans.Writer.Lazy.Writer Text) Text))

This brings up another issue which is that GHC sometimes shows names that are not in scope in its output. In this case you will get a second error that is probably understandable but not very nice:

Ginger.hs:21:34: error:
    Not in scope:
      type constructor or class ‘Control.Monad.Trans.Writer.Lazy.Writer’
    No module named ‘Control.Monad.Trans.Writer.Lazy’ is imported.
   |
21 |   let r = easyRender (ctxGVal :: Control.Monad.Trans.Writer.Lazy.Writer) tpl
   |                                  ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

It gets even worse if the transformers package is not exposed, then it will show transformers-0.5.6.2:Control.Monad.Trans.Writer.Lazy.Writer which is not valid Haskell syntax at all.

goldfirere commented 3 years ago

What a helpful report!

So, to extract out the actionable piece, you're proposing:

These arguments may need to mention out-of-scope entities, so the programmer will have to bring them into scope.

Here is the bit I would add to the error message:

To use this instance you can use `TypeApplications`:
        easyRender @_ @_ @(GVal (Run SourcePos (Control.Monad.Trans.Writer.Lazy.Writer Text) Text))
NB: You will have to bring 'Writer' into scope from 'Control.Monad.Trans.Writer.Lazy' using an 'import' statement.

Also, not applicable in this example, but there may also be a scoped type variable involved, where I would add

NB: You will have to bring type variable 's' into scope using 'ScopedTypeVariables'

I would be super-duper cool if we could have something where, when there are multiple instances, the user could click on one and then get this information for that one. But let's not let the super-duper cool get in the way of a small improvement.

noughtmare commented 3 years ago

I would be super-duper cool if we could have something where, when there are multiple instances, the user could click on one and then get this information for that one. But let's not let the super-duper cool get in the way of a small improvement.

Yeah, maybe this could be integrated into HLS in some way. Maybe with the structured error messages we could pass along detailed information for HLS to use to give more interactive error messages. For non HLS users we could add a flag -fsuggest-all-disambiguations or something to give the user the ability to request more of these disambiguation suggestions.

masaeedu commented 3 years ago

Kind of tangential, but I've always felt like the introductory text of the error message should say something about being unable to deduce an instance of a typeclass, instead of just presenting some inscrutable (secretly Constraint-kinded) type-level expression.

goldfirere commented 3 years ago

So @masaeedu, are you perhaps suggesting that, if the constraint is really a class constraint, we say something like "Could not find an instance matching ..." instead of "Could not deduce ..."? I agree that would be an improvement -- and a separate one from the main ticket here.

I currently see two GHC tickets that could be spun off from this Issue: the main ticket extracted from the OP and my comment, as well as the smaller (and easier to execute) suggestion from @masaeedu.

noughtmare commented 2 years ago

Now I'm running into issues with ambiguous type variables myself. I am using the x86-64bit library and get this error message:

ghci> movq (MemOp (Addr (Just rbp) (Just (-8)) NoIndex)) (MemOp (Addr (Just rbp) (Just (-16)) NoIndex))

<interactive>:6:1: error:
    • Ambiguous type variable ‘s0’ arising from a use of ‘movq’
      prevents the constraint ‘(IsSize s0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘s0’ should be.
      These potential instances exist:
        instance IsSize 'S1 -- Defined in ‘CodeGen.X86.Asm’
        instance IsSize 'S128 -- Defined in ‘CodeGen.X86.Asm’
        instance IsSize 'S16 -- Defined in ‘CodeGen.X86.Asm’
        ...plus three others
        (use -fprint-potential-instances to see them all)
    • In the expression:
        movq
          (MemOp (Addr (Just rbp) (Just (- 8)) NoIndex))
          (MemOp (Addr (Just rbp) (Just (- 16)) NoIndex))
      In an equation for ‘it’:
          it
            = movq
                (MemOp (Addr (Just rbp) (Just (- 8)) NoIndex))
                (MemOp (Addr (Just rbp) (Just (- 16)) NoIndex))

The type of movq is:

ghci> :t movq
movq
  :: (IsSize s, IsSize s') => Operand 'RW s -> Operand r s' -> Code

There are two constraints so I don't actually know which IsSize constraint is problematic.

Strangely, explicit type applications also don't work:

ghci> movq @S64 @S64 (MemOp (Addr (Just rbp) (Just (-8)) NoIndex)) (MemOp (Addr (Just rbp) (Just (-16)) NoIndex))

<interactive>:8:1: error:
    • Cannot apply expression of type ‘Operand 'RW s0
                                       -> Operand r0 s'0 -> Code’
      to a visible type argument ‘S64’
    • In the expression:
        movq
          @S64 @S64 (MemOp (Addr (Just rbp) (Just (- 8)) NoIndex))
          (MemOp (Addr (Just rbp) (Just (- 16)) NoIndex))
      In an equation for ‘it’:
          it
            = movq
                @S64 @S64 (MemOp (Addr (Just rbp) (Just (- 8)) NoIndex))
                (MemOp (Addr (Just rbp) (Just (- 16)) NoIndex))

Could GHC try to give some more information about where the ambiguous type variables come from?

Edit: I've figured out that both s and s' were ambiguous (it would be nice if GHC could report both), I guess GHC just likes to append 0 even if there is no confusion. I still don't know why type application doesn't work.

Ericson2314 commented 2 years ago

Rewinding a bit

instance ToGVal m (GVal m) -- Defined in ‘Text.Ginger.GVal

might be better as

instance m ~ n => ToGVal m (GVal n) -- Defined in ‘Text.Ginger.GVal

perhaps we should have something to steer library authors towards that? E.g. a language extension that desugars the former as the latter, as IMO the repeated variable thing is a more advanced concept despite having the more accessible syntax.


Back on topic, once we get visible type args, I think GHC should also propose adding such a parameter of those as a potential alternative, maybe the last one. Yes, it is probably not what the use wants, but it is arguable the "principle" or at least "least guess-ful" solution, thus deserves to be listed.

While visibilty type args behind a feature gate, we can simply hide this more exotic from regular uses unless that feature is enabled. Seems good enough to me to avoid it causing harm.