[commit: ghc] master: Comments reformating/corrections (d97e60f)

git at git.haskell.org git at git.haskell.org
Tue Aug 18 16:33:13 UTC 2015


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

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

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

commit d97e60f5dfab102127b6fa4a5277084815136fc7
Author: Divam <dfordivam at gmail.com>
Date:   Tue Aug 18 18:08:26 2015 +0200

    Comments reformating/corrections
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1145


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

d97e60f5dfab102127b6fa4a5277084815136fc7
 compiler/deSugar/Check.hs        | 47 ++++++++++++++++++++--------------------
 compiler/hsSyn/HsBinds.hs        |  2 +-
 compiler/parser/ApiAnnotation.hs |  2 +-
 3 files changed, 26 insertions(+), 25 deletions(-)

diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index d03e367..2835189 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -36,7 +36,7 @@ This module performs checks about if one list of equations are:
 \item Overlapped
 \item Non exhaustive
 \end{itemize}
-To discover that we go through the list of equations in a tree-like fashion.
+To discover this we go through the list of equations in a tree-like fashion.
 
 If you like theory, a similar algorithm is described in:
 \begin{quotation}
@@ -55,10 +55,10 @@ The algorithm is based on the first technique, but there are some differences:
 (By the way the second technique is really similar to the one used in
  @Match.hs@ to generate code)
 
-This function takes the equations of a pattern and returns:
+The @check@ function takes the equations of a pattern and returns:
 \begin{itemize}
 \item The patterns that are not recognized
-\item The equations that are not overlapped
+\item The equations that are shadowed or overlapped
 \end{itemize}
 It simplify the patterns and then call @check'@ (the same semantics), and it
 needs to reconstruct the patterns again ....
@@ -74,7 +74,7 @@ then all the constructors are equal:
   f (: x (: y []))   = ....
   f (: x xs)         = .....
 \end{verbatim}
-(more about that in @tidy_eqns@)
+(more about this in @tidy_eqns@)
 
 We would prefer to have a @WarningPat@ of type @String@, but Strings and the
 Pretty Printer are not friends.
@@ -175,26 +175,26 @@ untidy_lit (HsCharPrim src c) = HsChar src c
 untidy_lit lit                = lit
 
 {-
-This equation is the same that check, the only difference is that the
-boring work is done, that work needs to be done only once, this is
-the reason top have two functions, check is the external interface,
- at check'@ is called recursively.
+ at check@ is the external interface, boring work (tidy, untidy) is done
+in this as it needs to be done only once.
+ at check'@ is called recursively, this is the reason to have two functions.
 
-There are several cases:
+These are the several cases handled in @check'@:
 
 \begin{itemize}
 \item There are no equations: Everything is OK.
-\item There are only one equation, that can fail, and all the patterns are
+
+\item If all the patterns are variables and the match can't fail
+      then this equation is used and it doesn't generate non-exhaustive cases.
+
+\item There is only one equation that can fail, and all the patterns are
       variables. Then that equation is used and the same equation is
       non-exhaustive.
+
 \item All the patterns are variables, and the match can fail, there are
       more equations then the results is the result of the rest of equations
       and this equation is used also.
 
-\item The general case, if all the patterns are variables (here the match
-      can't fail) then the result is that this equation is used and this
-      equation doesn't generate non-exhaustive cases.
-
 \item In the general case, there can exist literals ,constructors or only
       vars in the first column, we actuate in consequence.
 
@@ -330,7 +330,7 @@ This equation takes a matrix of patterns and split the equations by
 constructor, using all the constructors that appears in the first column
 of the pattern matching.
 
-We can need a default clause or not ...., it depends if we used all the
+Whether we need a default clause or not depends if we used all the
 constructors or not explicitly. The reasoning is similar to @process_literals@,
 the difference is that here the default case is not always needed.
 -}
@@ -363,7 +363,7 @@ construct_matrix con qs =
     (pats,indexs) = (check' (remove_first_column con qs))
 
 {-
-Here remove first column is more difficult that with literals due to the fact
+Here removing the first column is more difficult (than literals) due to the fact
 that constructors can have arguments.
 
 For instance, the matrix
@@ -531,8 +531,8 @@ is_var_lit lit pat
 
 {-
 The difference beteewn @make_con@ and @make_whole_con@ is that
- at make_wole_con@ creates a new constructor with all their arguments, and
- at make_con@ takes a list of argumntes, creates the contructor getting their
+ at make_whole_con@ creates a new constructor with all their arguments, and
+ at make_con@ takes a list of arguments, creates the constructor getting their
 arguments from the list. See where \fbox{\ ???\ } are used for details.
 
 We need to reconstruct the patterns (make the constructors infix and
@@ -563,7 +563,7 @@ In particular:
 \\      @(x:(...:[])@ & returns to be & @[x,...]@
 \end{tabular}
 
-The difficult case is the third one becouse we need to follow all the
+The difficult case is the third one because we need to follow all the
 contructors until the @[]@ to know that we need to use the second case,
 not the second. \fbox{\ ???\ }
 -}
@@ -648,8 +648,8 @@ tidy_eqn eqn = eqn { eqn_pats = map tidy_pat (eqn_pats eqn),
 
 --------------
 might_fail_pat :: Pat Id -> Bool
--- Returns True of patterns that might fail (i.e. fall through) in a way
--- that is not covered by the checking algorithm.  Specifically:
+-- Returns True for patterns that might fail
+-- (that are not covered by the checking algorithm)  Specifically:
 --         NPlusKPat
 --         ViewPat (if refutable)
 --         ConPatOut of a PatSynCon
@@ -670,7 +670,8 @@ might_fail_pat (BangPat p)                   = might_fail_lpat p
 might_fail_pat (ConPatOut { pat_con = con, pat_args = ps })
   = case unLoc con of
     RealDataCon _dcon -> any might_fail_lpat (hsConPatArgs ps)
-    PatSynCon _psyn -> True
+    PatSynCon _psyn -> True -- This is considered 'might fail', as pattern synonym
+                            -- is not supported by checking algorithm
 
 -- Finally the ones that are sure to succeed, or which are covered by the checking algorithm
 might_fail_pat (LazyPat _)                   = False -- Always succeeds
@@ -696,7 +697,7 @@ tidy_pat (AsPat _ p)      = tidy_pat (unLoc p)
 tidy_pat (SigPatOut p _)  = tidy_pat (unLoc p)
 tidy_pat (CoPat _ pat _)  = tidy_pat pat
 
--- These two are might_fail patterns, so we map them to
+-- These are might_fail patterns, so we map them to
 -- WildPats.  The might_fail_pat stuff arranges that the
 -- guard says "this equation might fall through".
 tidy_pat (NPlusKPat id _ _ _) = WildPat (idType (unLoc id))
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs
index d934418..4b661ff 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/hsSyn/HsBinds.hs
@@ -289,7 +289,7 @@ That's where AbsBinds comes in.  It looks like this:
 
    AbsBinds { abs_tvs     = [a]
             , abs_exports = [ABE { abe_poly = M.reverse :: forall a. [a] -> [a],
-                                 , abe_mono = reverse :: a -> a}]
+                                 , abe_mono = reverse :: [a] -> [a]}]
             , abs_binds = { reverse :: [a] -> [a]
                                = \xs -> case xs of
                                             []     -> []
diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs
index 0c80ec7..5ae1d04 100644
--- a/compiler/parser/ApiAnnotation.hs
+++ b/compiler/parser/ApiAnnotation.hs
@@ -38,7 +38,7 @@ identifying the specific keyword being captured.
 
 So
 
-> let X = 1 in 2 *x
+> let x = 1 in 2 *x
 
 would result in the AST element
 



More information about the ghc-commits mailing list