[commit: ghc] master: Fix typo in accessor name (1b115b1)

git at git.haskell.org git at git.haskell.org
Mon Oct 30 14:01:18 UTC 2017


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

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

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

commit 1b115b16729a3414cc1e07fb1efe7f34c990b1f0
Author: Gabor Greif <ggreif at gmail.com>
Date:   Fri Oct 27 22:59:18 2017 +0200

    Fix typo in accessor name
    
    and in comments


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

1b115b16729a3414cc1e07fb1efe7f34c990b1f0
 compiler/deSugar/Check.hs                           | 6 +++---
 compiler/deSugar/DsBinds.hs                         | 2 +-
 compiler/specialise/SpecConstr.hs                   | 2 +-
 compiler/typecheck/TcType.hs                        | 2 +-
 libraries/base/GHC/IO/Encoding/CodePage/API.hs      | 4 ++--
 testsuite/mk/boilerplate.mk                         | 2 +-
 testsuite/tests/simplCore/should_compile/spec001.hs | 2 +-
 testsuite/tests/th/T10638.hs                        | 2 +-
 8 files changed, 11 insertions(+), 11 deletions(-)

diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index 8fb9553..d49a5c3 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -239,10 +239,10 @@ instance Monoid Provenance where
   mappend = (Semi.<>)
 
 data PartialResult = PartialResult {
-                        presultProvenence :: Provenance
+                        presultProvenance :: Provenance
                          -- keep track of provenance because we don't want
                          -- to warn about redundant matches if the result
-                         -- is contaiminated with a COMPLETE pragma
+                         -- is contaminated with a COMPLETE pragma
                       , presultCovered :: Covered
                       , presultUncovered :: Uncovered
                       , presultDivergent :: Diverged }
@@ -1640,7 +1640,7 @@ force_if True  pres = forces pres
 force_if False pres = pres
 
 set_provenance :: Provenance -> PartialResult -> PartialResult
-set_provenance prov pr = pr { presultProvenence = prov }
+set_provenance prov pr = pr { presultProvenance = prov }
 
 -- ----------------------------------------------------------------------------
 -- * Propagation of term constraints inwards when checking nested matches
diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index c01cb40..e11f580 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -655,7 +655,7 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl))
   = putSrcSpanDs loc $
     do { warnDs NoReason (text "Ignoring useless SPECIALISE pragma for NOINLINE function:"
                           <+> quotes (ppr poly_id))
-       ; return Nothing  }  -- Function is NOINLINE, and the specialiation inherits that
+       ; return Nothing  }  -- Function is NOINLINE, and the specialisation inherits that
                             -- See Note [Activation pragmas for SPECIALISE]
 
   | otherwise
diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs
index cfb9b5f..6115a03 100644
--- a/compiler/specialise/SpecConstr.hs
+++ b/compiler/specialise/SpecConstr.hs
@@ -1811,7 +1811,7 @@ that specialisations didn't fire inside wrappers; see test
 simplCore/should_compile/spec-inline.
 
 So now I just use the inline-activation of the parent Id, as the
-activation for the specialiation RULE, just like the main specialiser;
+activation for the specialisation RULE, just like the main specialiser;
 
 This in turn means there is no point in specialising NOINLINE things,
 so we test for that.
diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index 75e0215..b17df08 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -958,7 +958,7 @@ Moreover, consider
   inert item:  [G] b ~R f a
 We use anyRewritableTyVar to decide whether to kick out the inert item,
 on the grounds that the work item might rewrite it. Well, 'a' is certainly
-free in [G] b ~R f a.  But becuase the role of a type variable ('f' in
+free in [G] b ~R f a.  But because the role of a type variable ('f' in
 this case) is nominal, the work item can't actually rewrite the inert item.
 Moreover, if we were to kick out the inert item the exact same situation
 would re-occur and we end up with an infninite loop in which each kicks
diff --git a/libraries/base/GHC/IO/Encoding/CodePage/API.hs b/libraries/base/GHC/IO/Encoding/CodePage/API.hs
index f1d9d93..b31ebe9 100644
--- a/libraries/base/GHC/IO/Encoding/CodePage/API.hs
+++ b/libraries/base/GHC/IO/Encoding/CodePage/API.hs
@@ -285,7 +285,7 @@ cpEncode cp _max_char_size = \ibuf obuf -> do
     return (why2, mbuf', obuf)
 #else
     case why2 of
-      -- If we succesfully translate all of the UTF-16 buffer, we need to know why
+      -- If we successfully translate all of the UTF-16 buffer, we need to know why
       -- we weren't able to get any more UTF-16 out of the UTF-32 buffer
       InputUnderflow | isEmptyBuffer mbuf' -> return (why1, ibuf', obuf)
                      | otherwise           -> errorWithoutStackTrace "cpEncode: impossible underflown UTF-16 buffer"
@@ -361,7 +361,7 @@ bSearch msg code ibuf mbuf target_to_elems = go
       --
       -- Luckily if we have InvalidSequence/OutputUnderflow and we do not appear to have reached
       -- the target, what we should do is the same as normal because the fraction of ibuf that our
-      -- first "code" coded succesfully must be invalid-sequence-free, and ibuf will always
+      -- first "code" coded successfully must be invalid-sequence-free, and ibuf will always
       -- have been decoded as far as the first invalid sequence in it.
       case bufferElems mbuf `compare` target_to_elems of
         -- Coding n "from" chars from the input yields exactly as many "to" chars
diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk
index 0b684c7..c38bf85 100644
--- a/testsuite/mk/boilerplate.mk
+++ b/testsuite/mk/boilerplate.mk
@@ -54,7 +54,7 @@ ifeq "$(TEST_HC)" ""
 # Tests should be able to handle paths with spaces.
 #
 # One of the things ./validate (without --fast) does is check if binary
-# distributions can succesfully be installed and used in paths containing
+# distributions can successfully be installed and used in paths containing
 # spaces.
 #
 # It does so in the following way:
diff --git a/testsuite/tests/simplCore/should_compile/spec001.hs b/testsuite/tests/simplCore/should_compile/spec001.hs
index 9af452c..5fb9685 100644
--- a/testsuite/tests/simplCore/should_compile/spec001.hs
+++ b/testsuite/tests/simplCore/should_compile/spec001.hs
@@ -2,7 +2,7 @@
 {-# OPTIONS_GHC -O #-}
 
 -- In GHC 6.4, compiling this module gave a Core Lint failure following the
--- specialier, because a function was floated out that had a RULE that
+-- specialiser, because a function was floated out that had a RULE that
 -- mentioned another function (unpack, in fact).  but the latter wasn't
 -- floated because we didn't take the RULES into account properly; result,
 -- variable out of scope.
diff --git a/testsuite/tests/th/T10638.hs b/testsuite/tests/th/T10638.hs
index 7dd17eb..0cf2440 100644
--- a/testsuite/tests/th/T10638.hs
+++ b/testsuite/tests/th/T10638.hs
@@ -10,7 +10,7 @@ import GHC.Exts
    headers and the static keyword.
 -}
 
--- check that quasiquoting roundtrips succesfully and that the declaration
+-- check that quasiquoting roundtrips successfully and that the declaration
 -- does not include the static keyword
 test1 :: String
 test1 = $(do (ds@[ForeignD (ImportF _ _ p _ _)]) <-



More information about the ghc-commits mailing list