[GHC] #14675: GHC 8.4.1 regression: segfault when loading doctest on a module with ANNs on Ubuntu 16.04 or later

GHC ghc-devs at haskell.org
Tue Jan 16 04:31:59 UTC 2018


#14675: GHC 8.4.1 regression: segfault when loading doctest on a module with ANNs
on Ubuntu 16.04 or later
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:  8.4.1
          Component:  GHC API        |           Version:  8.4.1-alpha1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Runtime crash
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 As observed
 [https://github.com/ekmett/lens/issues/781#issuecomment-357841481 here],
 any attempt to run [https://hackage.haskell.org/package/doctest-0.13.0
 doctest] on a module that contains an `ANN` will result in a segfault—but
 only under certain settings! To explain better what I mean, let's look at
 a stripped-down version of `doctest`:

 {{{#!hs
 -- Bug.hs
 module Main (main) where

 import Control.Applicative ((<|>))
 import Control.Monad.IO.Class (liftIO)
 import Data.Char (isSpace)
 import Data.List (dropWhileEnd)
 import Digraph (flattenSCCs)
 import GHC (depanal, getSessionDynFlags, guessTarget, loadModule, noLoc,
             parseDynamicFlags, parseModule, runGhc, setSessionDynFlags,
             setTargets, topSortModuleGraph, typecheckModule)
 import System.Directory (findExecutable)
 import System.Process (readProcess)

 getLibDir :: IO FilePath
 getLibDir = do
   Just ghcPath <- findExecutable "ghc" <|> findExecutable "ghc-stage2"
   dropWhileEnd isSpace <$> readProcess ghcPath ["--print-libdir"] ""

 main :: IO ()
 main = do
   libdir <- getLibDir
   putStrLn libdir
   runGhc (Just libdir) $ do
     (dynflags, _, _) <- getSessionDynFlags >>= flip parseDynamicFlags (map
 noLoc ["-package base"])
     _ <- setSessionDynFlags dynflags
     mapM (`guessTarget` Nothing) ["Foo.hs"] >>= setTargets
     mods <- depanal [] False
     let sortedMods = flattenSCCs (topSortModuleGraph False mods Nothing)
     let f theMod = do liftIO $ putStrLn "Before parseModule"
                       m1 <- parseModule theMod
                       liftIO $ putStrLn "Before typecheckModule"
                       m2 <- typecheckModule m1
                       liftIO $ putStrLn "Before loadModule"
                       m3 <- loadModule m2
                       liftIO $ putStrLn "After loadModule"
                       return m3
     mods' <- mapM f sortedMods
     mods' `seq` return ()
 }}}

 As well as a module with an `ANN`:

 {{{#!hs
 module Foo where

 {-# ANN module "I'm an annotation" #-}
 }}}

 If you attempt to compile and run `Bug.hs` with GHC 8.2.2, everything is
 fine and dandy:

 {{{
 $ PATH=/opt/ghc/8.2.2/bin:$PATH ghc -fforce-recomp Bug.hs -package ghc
 [1 of 1] Compiling Main             ( Bug.hs, Bug.o )
 Linking Bug ...

 $ PATH=/opt/ghc/8.2.2/bin:$PATH ./Bug
 /opt/ghc/8.2.2/lib/ghc-8.2.2
 Before parseModule
 Before typecheckModule
 Before loadModule
 After loadModule
 }}}

 But if these two criteria are met:

 * You're using GHC 8.4.1-alpha
 * You're using Ubuntu 16.04 or later

 Then this will result in a segfault!

 {{{
 $ PATH=/opt/ghc/8.4.1/bin:$PATH ghc -fforce-recomp Bug.hs -package ghc
 [1 of 1] Compiling Main             ( Bug.hs, Bug.o )
 Linking Bug ...

 $ PATH=/opt/ghc/8.4.1/bin:$PATH ./Bug
 /opt/ghc/8.4.1/lib/ghc-8.4.0.20171222
 Before parseModule
 Before typecheckModule
 Segmentation fault (core dumped)

 $ lsb_release -a
 No LSB modules are available.
 Distributor ID: Ubuntu
 Description:    Ubuntu 17.04
 Release:        17.04
 Codename:       zesty
 }}}

 The second criteria about Ubuntu version is the most baffling part, but
 the segfault does not appear to occur when I try it on, for instance, an
 Ubuntu 14.04 machine:

 {{{
 $ PATH=/opt/ghc/8.4.1/bin:$PATH ghc -fforce-recomp Bug.hs -package ghc
 [1 of 1] Compiling Main             ( Bug.hs, Bug.o )
 Linking Bug ...

 $ PATH=/opt/ghc/8.4.1/bin:$PATH ./Bug
 /opt/ghc/8.4.1/lib/ghc-8.4.0.20171222
 Before parseModule
 Before typecheckModule
 Before loadModule
 After loadModule

 $ lsb_release -a
 No LSB modules are available.
 Distributor ID: Ubuntu
 Description:    Ubuntu 14.04.5 LTS
 Release:        14.04
 Codename:       trusty
 }}}

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


More information about the ghc-tickets mailing list