[commit: ghc] wip/T10137: Add haddock comments to all new exported top-level entities (e965edc)

git at git.haskell.org git at git.haskell.org
Tue Mar 17 15:05:18 UTC 2015


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

On branch  : wip/T10137
Link       : http://ghc.haskell.org/trac/ghc/changeset/e965edc31800b809eaa4266d8932f9af1000d95a/ghc

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

commit e965edc31800b809eaa4266d8932f9af1000d95a
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Mar 17 16:04:43 2015 +0100

    Add haddock comments to all new exported top-level entities
    
    (although it partly states the obvoius, and partly replicates
    information contained in the Notes.)


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

e965edc31800b809eaa4266d8932f9af1000d95a
 compiler/basicTypes/Literal.hs       |  2 ++
 compiler/cmm/CmmCreateSwitchPlans.hs |  2 ++
 compiler/cmm/CmmSwitch.hs            | 36 +++++++++++++++++++++++++-----------
 3 files changed, 29 insertions(+), 11 deletions(-)

diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs
index 08dfafe..ced05a4 100644
--- a/compiler/basicTypes/Literal.hs
+++ b/compiler/basicTypes/Literal.hs
@@ -271,6 +271,8 @@ isZeroLit (MachFloat  0) = True
 isZeroLit (MachDouble 0) = True
 isZeroLit _              = False
 
+-- | Returns the 'Integer' contained in the 'Literal', for when that makes
+-- sense, i.e. for 'Char', 'Int', 'Word' and 'LitInteger'.
 litValue  :: Literal -> Integer
 litValue (MachChar   c) = toInteger $ ord c
 litValue (MachInt    i) = i
diff --git a/compiler/cmm/CmmCreateSwitchPlans.hs b/compiler/cmm/CmmCreateSwitchPlans.hs
index 089839d..0fac30c 100644
--- a/compiler/cmm/CmmCreateSwitchPlans.hs
+++ b/compiler/cmm/CmmCreateSwitchPlans.hs
@@ -26,6 +26,8 @@ import DynFlags
 -- SwitchTargets, a data type exported abstractly by CmmSwitch.
 --
 
+-- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for
+-- code generation.
 cmmCreateSwitchPlans :: DynFlags -> CmmGraph -> UniqSM CmmGraph
 cmmCreateSwitchPlans dflags g = do
     blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g)
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs
index 130e7e4..800ee7d 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/cmm/CmmSwitch.hs
@@ -88,7 +88,9 @@ minJumpTableOffset = 2
 -- See switchTargetsToTable.
 
 
--- See Note [SwitchTargets]
+-- | A value of type SwitchTargets contains the alternatives for a 'CmmSwitch'
+-- value, and knows whether the value is signed, the possible range, an
+-- optional default value and a map from values to jump labels.
 data SwitchTargets =
     SwitchTargets
         Bool                       -- Signed values
@@ -97,10 +99,10 @@ data SwitchTargets =
         (M.Map Integer Label)      -- The branches
     deriving (Show, Eq)
 
--- mkSwitchTargets normalises the map a bit:
+-- | The smart constructr mkSwitchTargets normalises the map a bit:
 --  * No entries outside the range
 --  * No entries equal to the default
---  * No default if there is a range, and all elements have explicit values 
+--  * No default if all elements have explicit values
 mkSwitchTargets :: Bool -> (Integer, Integer) -> Maybe Label -> M.Map Integer Label -> SwitchTargets
 mkSwitchTargets signed range@(lo,hi) mbdef ids
     = SwitchTargets signed range mbdef' ids'
@@ -120,24 +122,29 @@ mkSwitchTargets signed range@(lo,hi) mbdef ids
     defaultNeeded = fromIntegral (M.size ids') /= hi-lo+1
 
 
+-- | Changes all labels mentioned in the SwitchTargets value
 mapSwitchTargets :: (Label -> Label) -> SwitchTargets -> SwitchTargets
 mapSwitchTargets f (SwitchTargets signed range mbdef branches)
     = SwitchTargets signed range (fmap f mbdef) (fmap f branches)
 
+-- | Returns the list of non-default branches of the SwitchTargets value
 switchTargetsCases :: SwitchTargets -> [(Integer, Label)]
 switchTargetsCases (SwitchTargets _ _ _ branches) = M.toList branches
 
+-- | Return the default label of the SwitchTargets value
 switchTargetsDefault :: SwitchTargets -> Maybe Label
 switchTargetsDefault (SwitchTargets _ _ mbdef _) = mbdef
 
+-- | Return the range of the SwitchTargets value
 switchTargetsRange :: SwitchTargets -> (Integer, Integer)
 switchTargetsRange (SwitchTargets _ range _ _) = range
 
+-- | Return whether this is used for a signed value
 switchTargetsSigned :: SwitchTargets -> Bool
 switchTargetsSigned (SwitchTargets signed _ _ _) = signed
 
--- switchTargetsToTable creates a dense jump table, usable for code generation.
--- Returns an offset to add to the value; the list is 0-based on the result
+-- | switchTargetsToTable creates a dense jump table, usable for code generation.
+-- Returns an offset to add to the value; the list is 0-based on the result.
 -- The conversion from Integer to Int is a bit of a wart, but works due to
 -- wrap-around arithmetic (as verified by the CmmSwitchTest test case).
 switchTargetsToTable :: SwitchTargets -> (Int, [Maybe Label])
@@ -174,6 +181,7 @@ switchTargetsToTable (SwitchTargets _ (lo,hi) mbdef branches)
 --             .quad   _c20q
 --             .quad   _c20r
 
+-- | The list of all labels occuring in the SwitchTargets value.
 switchTargetsToList :: SwitchTargets -> [Label]
 switchTargetsToList (SwitchTargets _ _ mbdef branches)
     = maybeToList mbdef ++ M.elems branches
@@ -187,6 +195,7 @@ switchTargetsFallThrough (SwitchTargets _ _ mbdef branches) = (groups, mbdef)
              groupBy ((==) `on` snd) $
              M.toList branches
 
+-- | Custom equality helper, needed for "CmmCommonBlockElim"
 eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool
 eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets signed2 range2 mbdef2 ids2) =
     signed1 == signed2 && range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2)
@@ -202,6 +211,15 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets
 -- Code generation for Switches
 
 
+-- | A SwitchPlan abstractly descries how a Switch statement ought to be
+-- implemented. See Note [createSwitchPlan]
+data SwitchPlan
+    = Unconditionally Label
+    | IfEqual Integer Label SwitchPlan
+    | IfLT Bool Integer SwitchPlan SwitchPlan
+    | JumpTable SwitchTargets
+  deriving Show
+--
 -- Note [createSwitchPlan]
 -- ~~~~~~~~~~~~~~~~~~~~~~~
 --
@@ -219,15 +237,11 @@ eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets
 --     findSingleValues
 --  5. The thus collected pieces are assembled to a balanced binary tree.
 
-data SwitchPlan
-    = Unconditionally Label 
-    | IfEqual Integer Label SwitchPlan
-    | IfLT Bool Integer SwitchPlan SwitchPlan
-    | JumpTable SwitchTargets
-  deriving Show
 
 type FlatSwitchPlan = SeparatedList Integer SwitchPlan
 
+-- | This function creates a SwitchPlan from a SwitchTargets value, breaking it
+-- down into smaller pieces suitable for code generation.
 createSwitchPlan :: SwitchTargets -> SwitchPlan
 createSwitchPlan (SwitchTargets signed mbdef range m) =
     -- pprTrace "createSwitchPlan" (text (show ids) $$ text (show (range,m)) $$ text (show pieces) $$ text (show flatPlan) $$ text (show plan)) $



More information about the ghc-commits mailing list