[commit: ghc] ghc-8.0: Fix some typos (b212af5)
git at git.haskell.org
git at git.haskell.org
Mon Jan 18 10:55:41 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.0
Link : http://ghc.haskell.org/trac/ghc/changeset/b212af56b0b4ec8b0db13bcb84225093f6751d59/ghc
>---------------------------------------------------------------
commit b212af56b0b4ec8b0db13bcb84225093f6751d59
Author: Rik Steenkamp <rik at ewps.nl>
Date: Sat Jan 16 13:18:53 2016 +0100
Fix some typos
Differential Revision: https://phabricator.haskell.org/D1785
(cherry picked from commit 148a50b5f8a9db4c3e2724540c41a7a7a10b3194)
>---------------------------------------------------------------
b212af56b0b4ec8b0db13bcb84225093f6751d59
compiler/coreSyn/CoreFVs.hs | 2 +-
compiler/hsSyn/HsBinds.hs | 2 +-
compiler/hsSyn/HsTypes.hs | 7 +++----
compiler/main/DynFlags.hs | 2 +-
compiler/rename/RnTypes.hs | 2 +-
compiler/typecheck/TcArrows.hs | 2 +-
compiler/typecheck/TcRnTypes.hs | 4 ++--
docs/users_guide/glasgow_exts.rst | 4 ++--
8 files changed, 12 insertions(+), 13 deletions(-)
diff --git a/compiler/coreSyn/CoreFVs.hs b/compiler/coreSyn/CoreFVs.hs
index 2e1c182..d3767e7 100644
--- a/compiler/coreSyn/CoreFVs.hs
+++ b/compiler/coreSyn/CoreFVs.hs
@@ -180,7 +180,7 @@ exprsSomeFreeVars fv_cand es =
addBndr :: CoreBndr -> FV -> FV
addBndr bndr fv fv_cand in_scope acc
= (varTypeTyCoVarsAcc bndr `unionFV`
- -- Include type varibles in the binder's type
+ -- Include type variables in the binder's type
-- (not just Ids; coercion variables too!)
FV.delFV bndr fv) fv_cand in_scope acc
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs
index e17f298..7901f10 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/hsSyn/HsBinds.hs
@@ -735,7 +735,7 @@ data Sig name
-- P :: forall a b. Prov => Req => ty
-- | A signature for a class method
- -- False: ordinary class-method signauure
+ -- False: ordinary class-method signature
-- True: default class method signature
-- e.g. class C a where
-- op :: a -> a -- Ordinary
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs
index e8b38c7..83161b3 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@ -123,7 +123,7 @@ This is the syntax for types as seen in type signatures.
Note [HsBSig binder lists]
~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider a binder (or pattern) decoarated with a type or kind,
+Consider a binder (or pattern) decorated with a type or kind,
\ (x :: a -> a). blah
forall (a :: k -> *) (b :: k). blah
Then we use a LHsBndrSig on the binder, so that the
@@ -140,7 +140,7 @@ is a bit complicated. Here's how it works.
* In a HsType,
HsForAllTy represents an /explicit, user-written/ 'forall'
e.g. forall a b. ...
- HsQualTy reprsents an /explicit, user-written/ context
+ HsQualTy represents an /explicit, user-written/ context
e.g. (Eq a, Show a) => ...
The context can be empty if that's what the user wrote
These constructors represent what the user wrote, no more
@@ -154,8 +154,7 @@ is a bit complicated. Here's how it works.
* HsImplicitBndrs is a wrapper that gives the implicitly-quantified
kind and type variables of the wrapped thing. It is filled in by
- the renamer. For example, if the
- user writes
+ the renamer. For example, if the user writes
f :: a -> a
the HsImplicitBinders binds the 'a' (not a HsForAllTy!).
NB: this implicit quantification is purely lexical: we bind any
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 491fd0d..8480332 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -2453,7 +2453,7 @@ dynamic_flags = [
, defFlag "dppr-cols" (intSuffix (\n d -> d{ pprCols = n }))
, defGhcFlag "dtrace-level" (intSuffix (\n d -> d{ traceLevel = n }))
-- Suppress all that is suppressable in core dumps.
- -- Except for uniques, as some simplifier phases introduce new varibles that
+ -- Except for uniques, as some simplifier phases introduce new variables that
-- have otherwise identical names.
, defGhcFlag "dsuppress-all"
(NoArg $ do setGeneralFlag Opt_SuppressCoercions
diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs
index 7a13cdc..4541d05 100644
--- a/compiler/rename/RnTypes.hs
+++ b/compiler/rename/RnTypes.hs
@@ -91,7 +91,7 @@ rnHsSigWcTypeScoped :: HsDocContext -> LHsSigWcType RdrName
rnHsSigWcTypeScoped ctx sig_ty thing_inside
= rn_hs_sig_wc_type False ctx sig_ty thing_inside
-- False: for pattern type sigs and rules we /do/ want
- -- to bring those type varibles into scope
+ -- to bring those type variables into scope
-- e.g \ (x :: forall a. a-> b) -> e
-- Here we do bring 'b' into scope
diff --git a/compiler/typecheck/TcArrows.hs b/compiler/typecheck/TcArrows.hs
index dac6aed..7f00d43 100644
--- a/compiler/typecheck/TcArrows.hs
+++ b/compiler/typecheck/TcArrows.hs
@@ -37,7 +37,7 @@ import Util
import Control.Monad
{-
-Note [Arrow overivew]
+Note [Arrow overview]
~~~~~~~~~~~~~~~~~~~~~
Here's a summary of arrows and how they typecheck. First, here's
a cut-down syntax:
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index fded11c..203396e 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -223,7 +223,7 @@ data Env gbl lcl
-- Includes all info about imported things
env_us :: {-# UNPACK #-} !(IORef UniqSupply),
- -- Unique supply for local varibles
+ -- Unique supply for local variables
env_gbl :: gbl, -- Info about things defined at the top level
-- of the module being compiled
@@ -2005,7 +2005,7 @@ Note [Shadowing in a constraint]
We assume NO SHADOWING in a constraint. Specifically
* The unification variables are all implicitly quantified at top
level, and are all unique
- * The skolem varibles bound in ic_skols are all freah when the
+ * The skolem variables bound in ic_skols are all freah when the
implication is created.
So we can safely substitute. For example, if we have
forall a. a~Int => ...(forall b. ...a...)...
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index 0b7696e..c6cacab 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -932,7 +932,7 @@ Given a pattern synonym definition of the form ::
it is assigned a *pattern type* of the form ::
- pattern P :: CReq => CProf => t1 -> t2 -> ... -> tN -> t
+ pattern P :: CReq => CProv => t1 -> t2 -> ... -> tN -> t
where ⟨CProv⟩ and ⟨CReq⟩ are type contexts, and ⟨t1⟩, ⟨t2⟩, ..., ⟨tN⟩
and ⟨t⟩ are types. Notice the unusual form of the type, with two
@@ -7976,7 +7976,7 @@ An implicit parameter is *bound* using the standard ``let`` or ``where``
binding forms. For example, we define the ``min`` function by binding
``cmp``. ::
- min :: [a] -> a
+ min :: Ord a => [a] -> a
min = let ?cmp = (<=) in least
A group of implicit-parameter bindings may occur anywhere a normal group
More information about the ghc-commits
mailing list