[GHC] #14120: stg-lint is hopelessly broken

GHC ghc-devs at haskell.org
Tue Aug 15 21:04:26 UTC 2017


#14120: stg-lint is hopelessly broken
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Today I spent a fair amount of time looking at the STG linter, having
 encountered a number of times in the past six months where I noticed it
 broke.

 While I thought fixing it would just be a few small tweaks, it seems that
 with every issue I fix another bug rears its ugly head. So far I have
 encountered and fixed,
  * #14116
  * #14117
  * #14118
 The solutions to each of these has seemed rather obvious. However, now I
 seem to have run into a bit of a more fundamental issue:

 Consider this excerpt extracted from `Foreign.Storable`,
 {{{#!hs
 {-# LANGUAGE BangPatterns #-}

 module Hi where

 import GHC.Word
 import GHC.Ptr
 import GHC.Base
 import GHC.Num
 import Data.Bits
 import GHC.Fingerprint.Type

 peekFingerprint :: Ptr Fingerprint -> IO Fingerprint
 peekFingerprint p0 = do
       let peekW64 :: Ptr Word8 -> Int -> Word64 -> IO Word64
           peekW64 _  0  !i = return i
           peekW64 !p !n !i = peekW64 (p `plusPtr` 1) (n-1) (i `shiftL` 8)

       high <- peekW64 (castPtr p0) 8 0
       low  <- peekW64 (castPtr p0 `plusPtr` 8) 8 0
       return (Fingerprint high low)
 }}}

 In particular notice the `castPtr` application. This triggers the STG
 linter with,
 {{{
 ghc-stage1: panic! (the 'impossible' happened)
   (GHC version 8.3.20170815 for x86_64-unknown-linux):
           *** Stg Lint ErrMsgs: in Stg2Stg ***
   <no location info>: warning:
        [in body of lambda with binders p0_s2zB :: Ptr Fingerprint,
                                        eta_s2zC :: State# RealWorld]
       In a function application, function type doesn't match arg types:
       Function type:
           Ptr Word8
           -> Int#
           -> Word#
           -> State# RealWorld
           -> (# State# RealWorld, Word64 #)
       Arg types:
           Ptr Fingerprint
           Int#
           Word#
           State# RealWorld
       Expression: $wpeekW64 p0_s2zB 8# 0## eta_s2zC
 }}}

 This is because by the time we are in Core Prep the `castPtr` is turned
 into a cast, which we discard in STG. Consequently, it seems that the
 comment attached to `stgEqType`,
 {{{#!hs
 stgEqType :: Type -> Type -> Bool
 -- Compare types, but crudely because we have discarded
 -- both casts and type applications, so types might look
 -- different but be the same.  So reply "True" if in doubt.
 -- "False" means that the types are definitely different.
 --
 -- Fundamentally this is a losing battle because of unsafeCoerce
 }}}
 is quite an understatement. Rather, there are exceedingly few cases where
 we can catch any type errors in STG. I think the only case which we can
 reliably catch is that of two types with explicitly different primreps.
 It's not clear what we can/should do about this.

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


More information about the ghc-tickets mailing list