[GHC] #9128: Possible bug in strictness analyzer when where clause declared NOINLINE

GHC ghc-devs at haskell.org
Mon May 19 20:48:20 UTC 2014


#9128: Possible bug in strictness analyzer when where clause declared NOINLINE
-----------------------------------------+---------------------------------
       Reporter:  aalevy                 |             Owner:
           Type:  bug                    |            Status:  new
       Priority:  normal                 |         Milestone:
      Component:  Compiler               |           Version:  7.8.2
       Keywords:  strictness bytestring  |  Operating System:
   Architecture:  Unknown/Multiple       |  Unknown/Multiple
     Difficulty:  Unknown                |   Type of failure:  Runtime
     Blocked By:                         |  crash
Related Tickets:                         |         Test Case:
                                         |          Blocking:
-----------------------------------------+---------------------------------
 I've encountered the following error message using a relatively straight
 forward library that wraps postgresql-simple in certain edge cases:


 {{{
 *** Exception: Oops!  Entered absent arg a_sYDl{v} [lid]
 bytestring-0.10.4.0:Data.ByteString.Internal.ByteString{tc r5T}
 }}}

 This happens on an invocation of a function, `dbSelect` under certain
 compilation conditions:

 {{{
 dbSelect :: (Model a) => Connection -> DBSelect a -> IO [a]
 {-# INLINE #-}
 dbSelect conn dbs = map lookupRow <$> query_ conn q
   where {-# NOINLINE #-}
     q = renderDBSelect dbs
 }}}

 A DBSelect is just a data-structure with different `Query` (wrapper around
 strict bytestring) fields for clauses in a SQL select query.
 `renderDBSelect` generates a single `Query` value from the DBSelect (by
 way of contructing a Blaze.Builder as an intermediate step).

 When compiled with no optimizations, this works fine, no issues. With -O1,
 I get the error above. The errors goes away, if I compile with -fno-
 strictness or remove the NOINLINE *or* INLINE pragmas.

 We've worked around this for now in the library by removgin the NOINLINE
 pragmas, but tracking this down it seems like the strictness analyzer
 might be falsly assuming `q` is never actually evaluated. For reference,
 this is a commit that still exhibits the bug:
 https://github.com/alevy/postgresql-
 orm/tree/93075d56ae5ffeb8f80ecc8c01436713c2656a6b

 I've also attached a small test application that excercises the bug.
 Because of how the library sets up a scratch database, the test
 application requires postgres and pg_ctl to be available in the path.

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


More information about the ghc-tickets mailing list