[GHC] #16195: Program with trivial polymorphism leads to out of scope dictionary

GHC ghc-devs at haskell.org
Wed Jan 16 16:07:01 UTC 2019


#16195: Program with trivial polymorphism leads to out of scope dictionary
-------------------------------------+-------------------------------------
           Reporter:  mpickering     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  high           |         Milestone:  8.8.1
          Component:  Compiler       |           Version:  8.7
           Keywords:                 |  Operating System:  Unknown/Multiple
  TypedTemplateHaskell               |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Almost certainly due to c2455e647501c5a382861196b64df3dd05b620a2

 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 ***
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16195>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list