Skip to content

Segfault compiling file that uses Template Haskell with -prof

Originally noticed here. Take the following two files:

{-# 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
{-# 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)
Trac metadata
Trac field Value
Version 8.4.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Profiling
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Edited by Ryan Scott
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information