
#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