diff --git a/client/ghc-debug-client.cabal b/client/ghc-debug-client.cabal
index 58a1c844daa18f336b0815f4339f359ad7a0c1a7..f8924e3b69e4105398939f408f2a7c9ae38f8980 100644
--- a/client/ghc-debug-client.cabal
+++ b/client/ghc-debug-client.cabal
@@ -51,7 +51,6 @@ library
bitwise ^>= 1.0,
hashable >= 1.3 && < 1.5,
mtl ^>= 2.2,
- eventlog2html == 0.9.3,
binary ^>= 0.8,
psqueues ^>= 0.2,
dom-lt ^>= 0.2,
diff --git a/client/src/GHC/Debug/Profile.hs b/client/src/GHC/Debug/Profile.hs
index b5dfbf3b97bdd32d3dc9683a94a0c6e924155dfd..969ab121d08df98aecb0523a201ad6a33de1c679 100644
--- a/client/src/GHC/Debug/Profile.hs
+++ b/client/src/GHC/Debug/Profile.hs
@@ -11,8 +11,7 @@
{-# LANGUAGE RecordWildCards #-}
{- | Functions for performing whole heap census in the style of the normal
- heap profiling -}
-module GHC.Debug.Profile( profile
- , censusClosureType
+module GHC.Debug.Profile( censusClosureType
, census2LevelClosureType
, closureCensusBy
, CensusByClosureType
@@ -32,18 +31,19 @@ import qualified Data.Map.Strict as Map
import Control.Monad.State
import Data.List (sortBy)
import Data.Ord
-import Control.Concurrent
-import Eventlog.Types
-import Eventlog.Data
-import Eventlog.Total
-import Eventlog.HtmlTemplate
-import Eventlog.Args (defaultArgs, Option(..))
import Data.Text (pack, Text, unpack)
import Data.Semigroup
import qualified Data.Text as T
import qualified Data.Map.Monoidal.Strict as MMap
import Data.Bitraversable
+--import Control.Concurrent
+--import Eventlog.Types
+--import Eventlog.Data
+--import Eventlog.Total
+--import Eventlog.HtmlTemplate
+--import Eventlog.Args (defaultArgs, Option(..))
+
type CensusByClosureType = Map.Map Text CensusStats
@@ -163,6 +163,7 @@ writeCensusByClosureType outpath c = do
writeFile outpath (unlines $ "key, total, count, max, avg" : map showLine res)
+{-
-- | Peform a profile at the given interval (in seconds), the result will
-- be rendered after each iteration using @eventlog2html@.
profile :: FilePath -> Int -> Debuggee -> IO ()
@@ -209,5 +210,6 @@ renderProfile ss = do
let html = templateString header data_json descs closure_descs as
writeFile "profile/ht.html" html
return ()
+ -}
diff --git a/test/Test.hs b/test/Test.hs
index cc4050387e797a91663e743a5024e0021956c73c..c4c11f64090de9b0593431bc684961adcd283f46 100644
--- a/test/Test.hs
+++ b/test/Test.hs
@@ -124,7 +124,6 @@ p26 :: Debuggee -> IO ()
p27 :: Debuggee -> IO ()
p28 :: Debuggee -> IO ()
p29 :: Debuggee -> IO ()
-p30 :: Debuggee -> IO ()
p31 :: Debuggee -> IO ()
p32 :: Debuggee -> IO ()
p33 :: Debuggee -> IO ()
@@ -298,7 +297,7 @@ p29 e = do
p29 e
-p30 e = profile "profile/profile_out.txt" 10_000 e
+--p30 e = profile "profile/profile_out.txt" 10_000 e
p31 e = analyseFragmentation 5_000_000 e