[GHC] #15529: runtime bug when profiling retainers

GHC ghc-devs at haskell.org
Mon Aug 27 22:58:26 UTC 2018


#15529: runtime bug when profiling retainers
-------------------------------------+-------------------------------------
        Reporter:  flip101           |                Owner:  (none)
            Type:  bug               |               Status:  patch
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.4.3
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):  Phab:D5075
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by monoidal):

 I've tried reducing the program so that we could add a testcase. However,
 the result still has 4 dependencies and it's very fragile. It converts a
 list to hashset and back; it has a function that ignores its argument; it
 uses verboseCheckWith with a property that is const True. If any of those
 are simplified, the panic disappears. I don't see a way to add a sensible
 test case based on it.

 For the record, the reduced program is below (needs QuickCheck, text,
 quickcheck-instances, unordered-containers).


 {{{
 #!hs
 {-# OPTIONS -Wall #-}

 module Main (main) where

 import qualified Data.HashSet as HS
 import qualified Data.Text.Lazy as T
 import Test.QuickCheck
 import Test.QuickCheck.Instances ()

 data T = Ter T.Text [T.Text] deriving (Show)

 letters :: HS.HashSet Char
 letters = HS.fromList ['a'..'z']

 arbitraryT :: () -> Gen T
 arbitraryT _ = do
   a <- elements (HS.toList letters)
   b <- arbitrary
   return $ Ter (T.singleton a) b

 data GroupTemplateDeclaration = GTD T T deriving (Show)

 instance Arbitrary GroupTemplateDeclaration where
   arbitrary = do
     a <- arbitraryT ()
     b <- arbitraryT ()
     return $ GTD a b

 qcr :: (GroupTemplateDeclaration -> Bool) -> IO ()
 qcr prop = verboseCheckWith (stdArgs { chatty = False }) (property . prop)

 main :: IO ()
 main = qcr (const True)
 }}}

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


More information about the ghc-tickets mailing list