[commit: packages/hpc] ghc-7.8: Tweak Haddock docs (1d4ec41)

git at git.haskell.org git at git.haskell.org
Sat Mar 22 11:29:08 UTC 2014


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

On branch  : ghc-7.8
Link       : http://git.haskell.org/packages/hpc.git/commitdiff/1d4ec41feee8299b13e7f6a5a072251b2894f238

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

commit 1d4ec41feee8299b13e7f6a5a072251b2894f238
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Mar 22 12:26:13 2014 +0100

    Tweak Haddock docs
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

1d4ec41feee8299b13e7f6a5a072251b2894f238
 Trace/Hpc/Mix.hs  |    9 +++++----
 Trace/Hpc/Tix.hs  |   21 +++++++++++----------
 Trace/Hpc/Util.hs |    6 +++---
 3 files changed, 19 insertions(+), 17 deletions(-)

diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs
index a02cd46..e5396b2 100644
--- a/Trace/Hpc/Mix.hs
+++ b/Trace/Hpc/Mix.hs
@@ -6,7 +6,7 @@
 -- Colin Runciman and Andy Gill, June 2006
 ---------------------------------------------------------------
 
--- | Datatypes and file-access routines for the per-module (.mix)
+-- | Datatypes and file-access routines for the per-module (@.mix@)
 -- indexes used by Hpc.
 module Trace.Hpc.Mix
         ( Mix(..)
@@ -34,10 +34,11 @@ import Trace.Hpc.Tix
 
 -- | 'Mix' is the information about a modules static properties, like
 -- location of Tix's in a file.
--- tab stops are the size of a tab in the provided line:colunm values.
+--
+-- Tab stops are the size of a tab in the provided /line:colunm/ values.
+--
 --  * In GHC, this is 1 (a tab is just a character)
---  * With hpc-tracer, this is 8 (a tab represents several spaces).
-
+--  * With @hpc-tracer@, this is 8 (a tab represents several spaces).
 data Mix = Mix
              FilePath           -- location of original file
              UTCTime            -- time of original file's last update
diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs
index 579d263..512c6c5 100644
--- a/Trace/Hpc/Tix.hs
+++ b/Trace/Hpc/Tix.hs
@@ -7,7 +7,7 @@
 ------------------------------------------------------------
 
 -- | Datatypes and file-access routines for the tick data file
--- used by HPC. (.tix)
+-- (@.tix@) used by Hpc.
 module Trace.Hpc.Tix(Tix(..), TixModule(..),
                      tixModuleName, tixModuleHash, tixModuleTixs,
                      readTix, writeTix, getTixFileName) where
@@ -15,18 +15,19 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..),
 import Data.List (isSuffixOf)
 import Trace.Hpc.Util (Hash, catchIO)
 
--- 'Tix ' is the storage format for our dynamic imformation about what
--- boxes are ticked.
+-- | 'Tix' is the storage format for our dynamic imformation about
+-- what boxes are ticked.
 data Tix = Tix [TixModule]
         deriving (Read, Show, Eq)
 
 data TixModule = TixModule
-                 String    -- module name
-                 Hash      -- hash number
-                 Int       -- length of tix list (allows pre-allocation at parse time).
+                 String    --  module name
+                 Hash      --  hash number
+                 Int       --  length of Tix list (allows pre-allocation at parse time).
                  [Integer] --  actual ticks
         deriving (Read, Show, Eq)
 
+-- TODO: Turn extractors below into proper 'TixModule' field-labels
 tixModuleName :: TixModule -> String
 tixModuleName (TixModule nm _ _ _) = nm
 tixModuleHash :: TixModule -> Hash
@@ -36,7 +37,7 @@ tixModuleTixs (TixModule  _ _ _ tixs) = tixs
 
 -- We /always/ read and write Tix from the current working directory.
 
--- read a Tix File.
+-- | Read a @.tix@ File.
 readTix :: String
         -> IO (Maybe Tix)
 readTix tix_filename =
@@ -44,7 +45,7 @@ readTix tix_filename =
               return $ Just $ read contents)
           (\ _ -> return $ Nothing)
 
--- write a Tix File.
+-- | Write a @.tix@ File.
 writeTix :: String
          -> Tix
          -> IO ()
@@ -56,8 +57,8 @@ tixName :: String -> String
 tixName name = name ++ ".tix"
 -}
 
--- getTixFullName takes a binary or .tix-file name,
--- and normalizes it into a .tix-file name.
+-- | 'getTixFullName' takes a binary or @.tix at -file name,
+-- and normalizes it into a @.tix at -file name.
 getTixFileName :: String -> String
 getTixFileName str | ".tix" `isSuffixOf` str
                    = str
diff --git a/Trace/Hpc/Util.hs b/Trace/Hpc/Util.hs
index 019f1c7..6846b2f 100644
--- a/Trace/Hpc/Util.hs
+++ b/Trace/Hpc/Util.hs
@@ -27,15 +27,15 @@ import Data.Word
 -- | 'HpcPos' is an Hpc local rendition of a Span.
 data HpcPos = P !Int !Int !Int !Int deriving (Eq, Ord)
 
--- | 'fromHpcPos' explodes the HpcPos into line:column-line:colunm
+-- | 'fromHpcPos' explodes the HpcPos into /line:column/-/line:colunm/
 fromHpcPos :: HpcPos -> (Int,Int,Int,Int)
 fromHpcPos (P l1 c1 l2 c2) = (l1,c1,l2,c2)
 
--- | 'toHpcPos' implodes to HpcPos, from line:column-line:colunm
+-- | 'toHpcPos' implodes to HpcPos, from /line:column/-/line:colunm/
 toHpcPos :: (Int,Int,Int,Int) -> HpcPos
 toHpcPos (l1,c1,l2,c2) = P l1 c1 l2 c2
 
--- | asks the question, is the first argument inside the second argument.
+-- | Predicate determining whether the first argument is inside the second argument.
 insideHpcPos :: HpcPos -> HpcPos -> Bool
 insideHpcPos small big =
              sl1 >= bl1 &&



More information about the ghc-commits mailing list