"README.md" did not exist on "5a9a49bef9828f11d602e51ba22abe46ae17f025"
ASSERT failed! when building ghc-debug-client with GHC HEAD
Attempting to build ghc-debug-client
with GHC HEAD (as as commit fc24c5cf) using a GHC build with assertions enabled will throw an ASSERT failed!
error. Here is a minimized version of ghc-debug-client
that triggers the issue:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module GHC.Debug.TypePointsFrom (detectLeaks) where
import Control.Monad (zipWithM_)
import Control.Monad.Reader (ReaderT(..))
import Control.Monad.State (StateT, evalStateT)
import qualified Data.Map as M
import qualified Data.Set as S
data Debuggee
newtype DebugM a = DebugM (ReaderT Debuggee IO a)
deriving (Functor, Applicative, Monad)
runSimple :: Debuggee -> DebugM a -> IO a
runSimple d (DebugM a) = runReaderT a d
cands :: [a]
cands = []
{-# NOINLINE cands #-}
detectLeaks :: Debuggee -> IO ()
detectLeaks e = loop M.empty
where
loop :: M.Map () RankInfo -> IO ()
loop rm = do
gs <- runSimple e $ mapM (findSlice rm) cands
zipWithM_ (\n _g -> writeFile
("slices/" ++ show @Int n ++ ".dot")
"abcd")
[0..] gs
loop rm
data RankInfo = RankInfo !Double !Int
lookupRM :: () -> M.Map () RankInfo -> [((), RankInfo)]
lookupRM k m = M.assocs filtered_map
where
(res_map, _) = M.partitionWithKey (\e _ -> e == k) m
filtered_map = M.filter (\(RankInfo r _) -> r > 0) res_map
findSlice :: forall m a. Monad m => M.Map () RankInfo -> () -> m [a]
findSlice rm _k = evalStateT go S.empty
where
go :: StateT s m [a]
go = do
let next_edges = lookupRM () rm
_ss <- concat <$> mapM (\_ -> go) next_edges
return []
$ ~/Software/ghc-9.11.20240504/bin/ghc -O Bug.hs -fforce-recomp
[1 of 1] Compiling GHC.Debug.TypePointsFrom ( Bug.hs, Bug.o )
WARNING:
Lost join point
bndr: loop_s5Ch
tc:
rules: []
Call stack:
CallStack (from HasCallStack):
warnPprTrace, called at compiler/GHC/Core/Opt/OccurAnal.hs:3902:5 in ghc-9.11-inplace:GHC.Core.Opt.OccurAnal
<no location info>: error:
ASSERT failed!
CallStack (from HasCallStack):
assert, called at compiler/GHC/Core/Opt/OccurAnal.hs:3853:10 in ghc-9.11-inplace:GHC.Core.Opt.OccurAnal