[commit: ghc] master: base: Document GHC.Stack.CCS internals (0b20d9c)

git at git.haskell.org git at git.haskell.org
Tue Nov 21 21:49:47 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0b20d9c51d627febab34b826fccf522ca8bac323/ghc

>---------------------------------------------------------------

commit 0b20d9c51d627febab34b826fccf522ca8bac323
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Tue Nov 21 14:27:51 2017 -0500

    base: Document GHC.Stack.CCS internals
    
    Reviewers: hvr
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D4204


>---------------------------------------------------------------

0b20d9c51d627febab34b826fccf522ca8bac323
 compiler/prelude/primops.txt.pp  |  2 +-
 libraries/base/GHC/Stack/CCS.hsc | 17 +++++++++++++++++
 2 files changed, 18 insertions(+), 1 deletion(-)

diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp
index 952d474..fe33ead 100644
--- a/compiler/prelude/primops.txt.pp
+++ b/compiler/prelude/primops.txt.pp
@@ -2836,7 +2836,7 @@ primop  GetCurrentCCSOp "getCurrentCCS#" GenPrimOp
    a -> State# s -> (# State# s, Addr# #)
    { Returns the current {\tt CostCentreStack} (value is {\tt NULL} if
      not profiling).  Takes a dummy argument which can be used to
-     avoid the call to {\tt getCCCS\#} being floated out by the
+     avoid the call to {\tt getCurrentCCS\#} being floated out by the
      simplifier, which would result in an uninformative stack
      ("CAF"). }
 
diff --git a/libraries/base/GHC/Stack/CCS.hsc b/libraries/base/GHC/Stack/CCS.hsc
index 51eb624..ba384a1 100644
--- a/libraries/base/GHC/Stack/CCS.hsc
+++ b/libraries/base/GHC/Stack/CCS.hsc
@@ -48,34 +48,50 @@ import GHC.List ( concatMap, reverse )
 #define PROFILING
 #include "Rts.h"
 
+-- | A cost-centre stack from GHC's cost-center profiler.
 data CostCentreStack
+
+-- | A cost-centre from GHC's cost-center profiler.
 data CostCentre
 
+-- | Returns the current 'CostCentreStack' (value is @nullPtr@ if the current
+-- program was not compiled with profiling support). Takes a dummy argument
+-- which can be used to avoid the call to @getCurrentCCS@ being floated out by
+-- the simplifier, which would result in an uninformative stack ("CAF").
 getCurrentCCS :: dummy -> IO (Ptr CostCentreStack)
 getCurrentCCS dummy = IO $ \s ->
    case getCurrentCCS## dummy s of
      (## s', addr ##) -> (## s', Ptr addr ##)
 
+-- | Get the 'CostCentreStack' associated with the given value.
 getCCSOf :: a -> IO (Ptr CostCentreStack)
 getCCSOf obj = IO $ \s ->
    case getCCSOf## obj s of
      (## s', addr ##) -> (## s', Ptr addr ##)
 
+-- | Run a computation with an empty cost-center stack. For example, this is
+-- used by the interpreter to run an interpreted computation without the call
+-- stack showing that it was invoked from GHC.
 clearCCS :: IO a -> IO a
 clearCCS (IO m) = IO $ \s -> clearCCS## m s
 
+-- | Get the 'CostCentre' at the head of a 'CostCentreStack'.
 ccsCC :: Ptr CostCentreStack -> IO (Ptr CostCentre)
 ccsCC p = (# peek CostCentreStack, cc) p
 
+-- | Get the tail of a 'CostCentreStack'.
 ccsParent :: Ptr CostCentreStack -> IO (Ptr CostCentreStack)
 ccsParent p = (# peek CostCentreStack, prevStack) p
 
+-- | Get the label of a 'CostCentre'.
 ccLabel :: Ptr CostCentre -> IO CString
 ccLabel p = (# peek CostCentre, label) p
 
+-- | Get the module of a 'CostCentre'.
 ccModule :: Ptr CostCentre -> IO CString
 ccModule p = (# peek CostCentre, module) p
 
+-- | Get the source span of a 'CostCentre'.
 ccSrcSpan :: Ptr CostCentre -> IO CString
 ccSrcSpan p = (# peek CostCentre, srcloc) p
 
@@ -92,6 +108,7 @@ ccSrcSpan p = (# peek CostCentre, srcloc) p
 currentCallStack :: IO [String]
 currentCallStack = ccsToStrings =<< getCurrentCCS ()
 
+-- | Format a 'CostCentreStack' as a list of lines.
 ccsToStrings :: Ptr CostCentreStack -> IO [String]
 ccsToStrings ccs0 = go ccs0 []
   where



More information about the ghc-commits mailing list