diff options
author | Gabor Greif <ggreif@gmail.com> | 2016-10-31 12:08:50 +0100 |
---|---|---|
committer | Gabor Greif <ggreif@gmail.com> | 2016-10-31 12:28:53 +0100 |
commit | 80d4a03332e09064e5542924f2897d7eb573f19e (patch) | |
tree | 34f1dcee354d631d5e2786d33f0b1bf7058e6f77 | |
parent | 7ddbdfd399a91eed410f3bd5a7caff2fd4bcce92 (diff) | |
download | haskell-80d4a03332e09064e5542924f2897d7eb573f19e.tar.gz |
Typos in comments
-rw-r--r-- | compiler/iface/MkIface.hs | 2 | ||||
-rw-r--r-- | compiler/rename/RnEnv.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcRnMonad.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcSMonad.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcTyClsDecls.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcType.hs | 2 | ||||
-rw-r--r-- | compiler/vectorise/Vectorise/Monad/Naming.hs | 2 | ||||
-rw-r--r-- | compiler/vectorise/Vectorise/Type/Env.hs | 2 | ||||
-rw-r--r-- | libraries/base/System/Console/GetOpt.hs | 2 | ||||
-rw-r--r-- | testsuite/tests/ffi/should_run/ffi005.hs | 2 | ||||
-rw-r--r-- | testsuite/tests/polykinds/T7332.hs | 4 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_compile/tc080.hs | 12 |
12 files changed, 18 insertions, 18 deletions
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 25e75ef3e5..9eac21c464 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -1024,7 +1024,7 @@ mkIfaceExports exports sort_flds = sortBy (stableNameCmp `on` flSelector) {- -Note [Orignal module] +Note [Original module] ~~~~~~~~~~~~~~~~~~~~~ Consider this: module X where { data family T } diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index b5f2463245..056f25c77c 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -1572,7 +1572,7 @@ respectively. Initially, we just store the "standard" name (PrelNames.fromInteg fromRationalName etc), but the renamer changes this to the appropriate user name if Opt_NoImplicitPrelude is on. That is what lookupSyntaxName does. -We treat the orignal (standard) names as free-vars too, because the type checker +We treat the original (standard) names as free-vars too, because the type checker checks the type of the user thing against the type of the standard thing. -} diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index e4fdd9c233..d3ae05861b 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1123,7 +1123,7 @@ error to report. So this capture-the-emit dance isn't as stupid as it looks :-). However suppose we throw an exception inside an invocation of -captureConstraints. Then we'll discard all the costraints. But some +captureConstraints. Then we'll discard all the constraints. But some of those contraints might be "variable out of scope" Hole constraints, and that might have been the actual original cause of the exception! For example (Trac #12529): diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 504bc66533..0d20122553 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -607,7 +607,7 @@ data InertCans -- See Note [Detailed InertCans Invariants] for more , inert_safehask :: DictMap Ct -- Failed dictionary resolution due to Safe Haskell overlapping - -- instances restriction. We keep this seperate from inert_dicts + -- instances restriction. We keep this separate from inert_dicts -- as it doesn't cause compilation failure, just safe inference -- failure. -- diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 734a3a39c0..aa6d44f65e 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -742,7 +742,7 @@ tcTyClDecl1 _parent roles_info , tcdATs = ats, tcdATDefs = at_defs }) = ASSERT( isNothing _parent ) do { clas <- fixM $ \ clas -> - -- We need the knot becase 'clas' is passed into tcClassATs + -- We need the knot because 'clas' is passed into tcClassATs tcTyClTyVars class_name $ \ binders res_kind -> do { MASSERT( isConstraintKind res_kind ) ; traceTc "tcClassDecl 1" (ppr class_name $$ ppr binders) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index e5c03bfa3f..4dbe4a3d21 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -303,7 +303,7 @@ data InferResult , ir_lvl :: TcLevel -- See Note [TcLevel of ExpType] in TcMType , ir_inst :: Bool -- True <=> deeply instantiate before returning -- i.e. return a RhoType - -- False <=> do not instantaite before returning + -- False <=> do not instantiate before returning -- i.e. return a SigmaType , ir_ref :: IORef (Maybe TcType) } -- The type that fills in this hole should be a Type, diff --git a/compiler/vectorise/Vectorise/Monad/Naming.hs b/compiler/vectorise/Vectorise/Monad/Naming.hs index 1cb8d87bcf..0b46416ddb 100644 --- a/compiler/vectorise/Vectorise/Monad/Naming.hs +++ b/compiler/vectorise/Vectorise/Monad/Naming.hs @@ -35,7 +35,7 @@ import Control.Monad -- |Create a localised variant of a name, using the provided function to transform its `OccName`. -- --- If the name external, encode the orignal name's module into the new 'OccName'. The result is +-- If the name external, encode the original name's module into the new 'OccName'. The result is -- always an internal system name. -- mkLocalisedName :: (Maybe String -> OccName -> OccName) -> Name -> VM Name diff --git a/compiler/vectorise/Vectorise/Type/Env.hs b/compiler/vectorise/Vectorise/Type/Env.hs index 421b1dde9a..d70de485fe 100644 --- a/compiler/vectorise/Vectorise/Type/Env.hs +++ b/compiler/vectorise/Vectorise/Type/Env.hs @@ -330,7 +330,7 @@ vectTypeEnv tycons vectTypeDecls vectClassDecls } -- Add a mapping from the original to vectorised type constructor to the vectorisation map. - -- Unless the type constructor is abstract, also mappings from the orignal's data constructors + -- Unless the type constructor is abstract, also mappings from the original's data constructors -- to the vectorised type's data constructors. -- -- We have three cases: (1) original and vectorised type constructor are the same, (2) the diff --git a/libraries/base/System/Console/GetOpt.hs b/libraries/base/System/Console/GetOpt.hs index 3f36f1f7b3..38cccc2ed4 100644 --- a/libraries/base/System/Console/GetOpt.hs +++ b/libraries/base/System/Console/GetOpt.hs @@ -124,7 +124,7 @@ data OptKind a -- kind of cmd line arg (internal use only): -- second argument. usageInfo :: String -- header -> [OptDescr a] -- option descriptors - -> String -- nicely formatted decription of options + -> String -- nicely formatted description of options usageInfo header optDescr = unlines (header:table) where (ss,ls,ds) = (unzip3 . concatMap fmtOpt) optDescr table = zipWith3 paste (sameLen ss) (sameLen ls) ds diff --git a/testsuite/tests/ffi/should_run/ffi005.hs b/testsuite/tests/ffi/should_run/ffi005.hs index 63de9558f9..9c17441954 100644 --- a/testsuite/tests/ffi/should_run/ffi005.hs +++ b/testsuite/tests/ffi/should_run/ffi005.hs @@ -1,4 +1,4 @@ --- !!! test for foreign import dynamic/wrapper, orignally by Alastair Reid, +-- !!! test for foreign import dynamic/wrapper, originally by Alastair Reid, -- with a few changes to get it to run on GHC by Simon Marlow. import Foreign hiding ( unsafePerformIO ) diff --git a/testsuite/tests/polykinds/T7332.hs b/testsuite/tests/polykinds/T7332.hs index a18b32b838..0d3e7e5a13 100644 --- a/testsuite/tests/polykinds/T7332.hs +++ b/testsuite/tests/polykinds/T7332.hs @@ -63,8 +63,8 @@ hence Now things are delicate. Either the instance Monoid (DC d) will fire or, if we are lucky, we might spot that (Monoid (DC d)) is a superclass of a given. But now (Decl 15) we add superclasses lazily, so that is less -likely to happen, and was always fragile. So include (MOnoid d) in the -signature, as was the case in the orignal ticket. +likely to happen, and was always fragile. So include (Monoid d) in the +signature, as was the case in the original ticket. -} diff --git a/testsuite/tests/typecheck/should_compile/tc080.hs b/testsuite/tests/typecheck/should_compile/tc080.hs index 78e413ffd9..8b08d2d584 100644 --- a/testsuite/tests/typecheck/should_compile/tc080.hs +++ b/testsuite/tests/typecheck/should_compile/tc080.hs @@ -1,4 +1,4 @@ ---module Parse(Parse(..),whiteSpace,seperatedBy) where +--module Parse(Parse(..),whiteSpace,separatedBy) where --import StdLib module ShouldSucceed where @@ -27,14 +27,14 @@ instance Parse Char where forced n = True instance (Parse a) => Parse [a] where - parseType more = (map parseLine (seperatedBy ',' (l++",")),out) + parseType more = (map parseLine (separatedBy ',' (l++",")),out) where (l,']':out) = span' (\x->x/=']') (tail more) forced = all forced -seperatedBy :: Char -> String -> [String] -seperatedBy ch [] = [] -seperatedBy ch xs = twaddle ch (span' (\x->x/=ch) xs) - where twaddle ch (l,_:r) = l:seperatedBy ch r +separatedBy :: Char -> String -> [String] +separatedBy ch [] = [] +separatedBy ch xs = twaddle ch (span' (\x->x/=ch) xs) + where twaddle ch (l,_:r) = l:separatedBy ch r whiteSpace :: String -> String whiteSpace = dropWhile isSpace |