diff options
| -rw-r--r-- | libraries/ghci/GHCi/Message.hs | 2 | ||||
| -rw-r--r-- | libraries/ghci/GHCi/Run.hs | 31 |
2 files changed, 17 insertions, 16 deletions
diff --git a/libraries/ghci/GHCi/Message.hs b/libraries/ghci/GHCi/Message.hs index 6e31a95f9a..d660c10932 100644 --- a/libraries/ghci/GHCi/Message.hs +++ b/libraries/ghci/GHCi/Message.hs @@ -474,7 +474,7 @@ instance Binary Heap.TsoFlags instance Binary Heap.StgInfoTable instance Binary Heap.ClosureType instance Binary Heap.PrimType -instance (Binary a) => Binary (Heap.GenClosure a) +instance Binary a => Binary (Heap.GenClosure a) data Msg = forall a . (Binary a, Show a) => Msg (Message a) diff --git a/libraries/ghci/GHCi/Run.hs b/libraries/ghci/GHCi/Run.hs index cde889158d..4ecb64620a 100644 --- a/libraries/ghci/GHCi/Run.hs +++ b/libraries/ghci/GHCi/Run.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE GADTs, RecordWildCards, MagicHash, ScopedTypeVariables, CPP, UnboxedTuples #-} +{-# LANGUAGE GADTs, RecordWildCards, MagicHash, ScopedTypeVariables, CPP, + UnboxedTuples #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -- | @@ -372,21 +373,21 @@ mkString0 bs = B.unsafeUseAsCStringLen bs $ \(cstr,len) -> do return (castRemotePtr (toRemotePtr ptr)) mkCostCentres :: String -> [(String,String)] -> IO [RemotePtr CostCentre] - - - - - - - - - - - - - +#if defined(PROFILING) +mkCostCentres mod ccs = do + c_module <- newCString mod + mapM (mk_one c_module) ccs + where + mk_one c_module (decl_path,srcspan) = do + c_name <- newCString decl_path + c_srcspan <- newCString srcspan + toRemotePtr <$> c_mkCostCentre c_name c_module c_srcspan + +foreign import ccall unsafe "mkCostCentre" + c_mkCostCentre :: Ptr CChar -> Ptr CChar -> Ptr CChar -> IO (Ptr CostCentre) +#else mkCostCentres _ _ = return [] - +#endif getIdValFromApStack :: HValue -> Int -> IO (Maybe HValue) getIdValFromApStack apStack (I# stackDepth) = do |
