[GHC] #15036: STG Linter dies when linting primitive

GHC ghc-devs at haskell.org
Sat Apr 14 14:07:21 UTC 2018


#15036: STG Linter dies when linting primitive
-------------------------------------+-------------------------------------
        Reporter:  andrewthad        |                Owner:  (none)
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.4.1
      Resolution:  duplicate         |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #14787            |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * status:  new => closed
 * resolution:   => duplicate
 * related:   => #14787


Comment:

 This can be reduced down to:

 {{{#!hs
 module Bug where

 foreign import ccall unsafe "wat" wat :: IO ()
 }}}
 {{{
 $ ghc Bug.hs -dstg-lint -fforce-recomp
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.1 for x86_64-unknown-linux):
           *** Stg Lint ErrMsgs: in Unarise ***
   <no location info>: warning:
        [in body of lambda with binders void_0E :: Void#]
       In some algebraic case alternative, constructor is not a constructor
 of scrutinee type:
       (# State# RealWorld #)
       (##)
   *** Offending Program ***
   $trModule1_r1b1 :: Addr#
   [GblId, Caf=NoCafRefs, Unf=OtherCon []] =
       "main"#;

   $trModule2_r1bm :: TrName
   [GblId, Caf=NoCafRefs, Unf=OtherCon []] =
       CCS_DONT_CARE TrNameS! [$trModule1_r1b1];

   $trModule3_r1bn :: Addr#
   [GblId, Caf=NoCafRefs, Unf=OtherCon []] =
       "Bug"#;

   $trModule4_r1bo :: TrName
   [GblId, Caf=NoCafRefs, Unf=OtherCon []] =
       CCS_DONT_CARE TrNameS! [$trModule3_r1bn];

   $trModule :: Module
   [GblId, Caf=NoCafRefs, Unf=OtherCon []] =
       CCS_DONT_CARE Module! [$trModule2_r1bm $trModule4_r1bo];

   wat1_r1bp :: State# RealWorld -> (# State# RealWorld, () #)
   [GblId, Arity=1, Caf=NoCafRefs, Unf=OtherCon []] =
       sat-only [] \r [void_0E]
           case __pkg_ccall main [void#] of { (##) -> Unit# [()]; };

   wat :: IO ()
   [GblId, Arity=1, Caf=NoCafRefs, Unf=OtherCon []] =
       [] \r [void_0E] wat1_r1bp void#;
   *** End of Offense ***
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/stgSyn/StgLint.hs:68:19 in
 ghc:StgLint
 }}}

 However, osa1 fixed this in #14787—and indeed, `primitive` builds on GHC
 HEAD with `-dstg-lint`, both in version 0.6.3.0 and upstream—so closing.

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


More information about the ghc-tickets mailing list