Program with trivial polymorphism leads to out of scope dictionary
Almost certainly due to c2455e64
A trivial program now causes a core lint error due to an out-of-scope dictionary.
module A where
foo :: Code (IO ())
foo = [|| return () ||]
module B where
main :: IO ()
main = $$foo
*** Core Lint errors : in result of Desugar (before optimization) ***
<no location info>: warning:
In the expression: return @ IO $dMonad_a4od @ () ()
Out of scope: $dMonad_a4od :: Monad m_a4oc[tau:0]
[LclId]
*** Offending Program ***
Rec {
$trModule :: Module
[LclIdX]
$trModule = Module (TrNameS "main"#) (TrNameS "B"#)
main :: IO ()
[LclIdX]
main = return @ IO $dMonad_a4od @ () ()
end Rec }
*** End of Offense ***
Trac metadata
Trac field | Value |
---|---|
Version | 8.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | high |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |