[GHC] #14931: Segfault compiling files with -fprof-all

#14931: Segfault compiling files with -fprof-all -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Originally noticed [https://github.com/llvm-hs/llvm- hs/issues/86#issuecomment-373710312 here]. Take the following two files: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} module State (MonadState(..), Lazy.evalState) where import qualified Control.Monad.Trans.State.Lazy as Lazy (StateT, get, put, evalState) class Monad m => MonadState s m | m -> s where get :: m s put :: s -> m () instance Monad m => MonadState s (Lazy.StateT s m) where get = Lazy.get put = Lazy.put }}} {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Prelude (Int, IO, Bool(..), Num(..), Monad(..), not, print) import qualified Language.Haskell.TH.Syntax as TH import State wat :: IO () wat = print $(let playGame [] = do (_, score) <- get return score playGame (x:xs) = do (on, score) <- get case x of 'a' | on -> put (on, score + 1) 'b' | on -> put (on, score - 1) 'c' -> put (not on, score) _ -> put (on, score) playGame xs startState :: (Bool, Int) startState = (False, 0) in TH.lift (evalState (playGame "abcaaacbbcabbab") startState) ) }}} Compiling them like so leads to a segfault: {{{ $ ~/Software/ghc-8.4.1/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs -fprof-auto $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs Segmentation fault (core dumped) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling files with -fprof-all -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This bug has an interesting history. On GHC 8.0.2, doing the same thing yielded [https://github.com/llvm-hs/llvm- hs/issues/86#issuecomment-301194192 this error]: {{{ $ /opt/ghc/8.0.2/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ /opt/ghc/8.0.2/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs -fprof-auto $ /opt/ghc/8.0.2/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: State_zdfMonadStatesStateTzuzdcget_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs@haskell.org }}} However, on GHC 8.2.1 and 8.2.2, it appeared to work without issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling files with -fprof-auto -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling files with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, `-fprof-auto` has nothing to do with this—you can reproduce the issue with simply `-prof`: {{{ $ ~/Software/ghc-8.4.1/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs Segmentation fault (core dumped) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I forgot that `mtl` is bundled with GHC now, so you can reproduce this with a single file: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Prelude (Int, IO, Bool(..), Num(..), Monad(..), not, print) import qualified Language.Haskell.TH.Syntax as TH import Control.Monad.State wat :: IO () wat = print $(let playGame [] = do (_, score) <- get return score playGame (x:xs) = do (on, score) <- get case x of 'a' | on -> put (on, score + 1) 'b' | on -> put (on, score - 1) 'c' -> put (not on, score) _ -> put (on, score) playGame xs startState :: (Bool, Int) startState = (False, 0) in TH.lift (evalState (playGame "abcaaacbbcabbab") startState) ) }}} {{{ $ ~/Software/ghc-8.4.1/bin/ghc -O -prof -osuf p_o -hisuf p_hi Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.p_o ) Segmentation fault (core dumped) }}} Also, Template Haskell appears to be a key ingredient here, since removing it makes the issue go away. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nmattia): Ok, this is really strange. I've tried to reproduce the example given in https://ghc.haskell.org/trac/ghc/ticket/8025. In this case, GHC 8.0.2 and 8.2.2 fail with {{{ ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: ... }}} while 8.4.1 (actually, [8.4.0 https://github.com/NixOS/nixpkgs/issues/37026]) ) compiles successfully: {{{ nicolas@nicolas-XPS-13-9370:/tmp/no-code$ cat A.hs {-# LANGUAGE TemplateHaskell #-} module A where a = [|3|] nicolas@nicolas-XPS-13-9370:/tmp/no-code$ cat B.hs {-# LANGUAGE TemplateHaskell #-} module B where import A x = $(a) nicolas@nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc802' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, nothing ) [2 of 2] Compiling B ( B.hs, nothing ) ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: A_a_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs@haskell.org nicolas@nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc822' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, nothing ) [2 of 2] Compiling B ( B.hs, nothing ) ghc: ^^ Could not load 'A_a_closure', dependency unresolved. See top entry above. ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: A_a_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs@haskell.org nicolas@nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc841' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, /run/user/1001/ghc17566_0/ghc_2.o ) [2 of 2] Compiling B ( B.hs, /run/user/1001/ghc17566_0/ghc_4.o ) nicolas@nicolas-XPS-13-9370:/tmp/no-code$ echo $? 0 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a version which doesn't depend on `mtl`: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Data.Functor.Identity (runIdentity) import Language.Haskell.TH.Syntax (lift) wat :: IO () wat = print $(lift $ runIdentity $ do (_, x) <- return (True, False) return x) }}} {{{ $ ~/Software/ghc-8.4.1/bin/ghc -O -prof -osuf p_o -hisuf p_hi Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.p_o ) Segmentation fault (core dumped) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest * milestone: => 8.4.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Given that annotations and template haskell are handled in a similar way, I'm thinking there is a possibility that this could be related to #14675 (see comment 22 & 23 for a summary) and similar tickets. However, 8.4.1 shipped with a workaround... which might break things here? Or some other commits since 8.2.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): This works with GHC HEAD.
However, 8.4.1 shipped with a workaround
GHC 8.4.1 is shipped without some of the commits that were supposed to be included, e.g. #14868 is also broken in 8.4.1 even though the fix was merged to the branch. This may be another such case where the commit was merged to the branch but not included in the release somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): We now think this is fixed by the same patch as #14705 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14705 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #14705 Comment: This looks to be #14705. Sadly the fix for this didn't quite make it in to 8.4.1 due to administrative error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: #14705 => Comment: Add regression test from comment:6 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14931#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14931: Segfault compiling file that uses Template Haskell with -prof
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: closed
Priority: highest | Milestone: 8.4.2
Component: Profiling | Version: 8.4.1
Resolution: duplicate | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC