diff options
author | Krzysztof Gogolewski <krz.gogolewski@gmail.com> | 2013-10-12 18:39:54 +0200 |
---|---|---|
committer | Krzysztof Gogolewski <krz.gogolewski@gmail.com> | 2013-10-12 18:39:54 +0200 |
commit | 77d2aa5fd4ab6e20f84f3725e7ae6a65fb18d5a1 (patch) | |
tree | 1a60967aa53716fd5abe203aebfaf44fe4efe72b | |
parent | c5262a12a2d3568cc00ffa47a686b3c8e015b2c5 (diff) | |
download | haskell-77d2aa5fd4ab6e20f84f3725e7ae6a65fb18d5a1.tar.gz |
Typos
-rw-r--r-- | compiler/cmm/CmmSink.hs | 2 | ||||
-rw-r--r-- | compiler/coreSyn/PprCore.lhs | 2 | ||||
-rw-r--r-- | compiler/deSugar/DsExpr.lhs | 2 | ||||
-rw-r--r-- | compiler/deSugar/MatchLit.lhs | 2 | ||||
-rw-r--r-- | compiler/ghci/RtClosureInspect.hs | 2 | ||||
-rw-r--r-- | compiler/main/HscTypes.lhs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 2 | ||||
-rw-r--r-- | compiler/parser/Lexer.x | 2 | ||||
-rw-r--r-- | compiler/prelude/PrimOp.lhs | 2 | ||||
-rw-r--r-- | compiler/simplCore/OccurAnal.lhs | 2 | ||||
-rw-r--r-- | compiler/specialise/Specialise.lhs | 2 | ||||
-rw-r--r-- | compiler/types/Type.lhs | 2 | ||||
-rw-r--r-- | compiler/utils/Pretty.lhs | 2 | ||||
-rw-r--r-- | compiler/vectorise/Vectorise/Monad/Local.hs | 2 |
14 files changed, 14 insertions, 14 deletions
diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index 58cbef8568..17b72c0f99 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -565,7 +565,7 @@ localRegistersConflict dflags expr node = -- We will attempt to sink { x = R1 } but we will detect conflict with -- { P64[Sp - 8] = x } and hence we will drop { x = R1 } without even -- checking whether it conflicts with { call f() }. In this way we will --- never need to check any assignment conflicts with CmmCall. Remeber +-- never need to check any assignment conflicts with CmmCall. Remember -- that we still need to check for potential memory conflicts. -- -- So the result is that we only need to worry about CmmUnsafeForeignCall nodes diff --git a/compiler/coreSyn/PprCore.lhs b/compiler/coreSyn/PprCore.lhs index 00f9a9346f..1868a320d2 100644 --- a/compiler/coreSyn/PprCore.lhs +++ b/compiler/coreSyn/PprCore.lhs @@ -108,7 +108,7 @@ ppr_expr :: OutputableBndr b => (SDoc -> SDoc) -> Expr b -> SDoc -- an atomic value (e.g. function args) ppr_expr _ (Var name) = ppr name -ppr_expr add_par (Type ty) = add_par (ptext (sLit "TYPE") <+> ppr ty) -- Wierd +ppr_expr add_par (Type ty) = add_par (ptext (sLit "TYPE") <+> ppr ty) -- Weird ppr_expr add_par (Coercion co) = add_par (ptext (sLit "CO") <+> ppr co) ppr_expr add_par (Lit lit) = pprLiteral add_par lit diff --git a/compiler/deSugar/DsExpr.lhs b/compiler/deSugar/DsExpr.lhs index c7d7bc300b..6d78d33d44 100644 --- a/compiler/deSugar/DsExpr.lhs +++ b/compiler/deSugar/DsExpr.lhs @@ -838,7 +838,7 @@ warnDiscardedDoBindings rhs rhs_ty -> warnDs (wrongMonadBind rhs elt_ty) _ -> return () } } - | otherwise -- RHS does have type of form (m ty), which is wierd + | otherwise -- RHS does have type of form (m ty), which is weird = return () -- but at lesat this warning is irrelevant unusedMonadBind :: LHsExpr Id -> Type -> SDoc diff --git a/compiler/deSugar/MatchLit.lhs b/compiler/deSugar/MatchLit.lhs index f4c9465f02..b888b790d1 100644 --- a/compiler/deSugar/MatchLit.lhs +++ b/compiler/deSugar/MatchLit.lhs @@ -265,7 +265,7 @@ tidyNPat tidy_lit_pat (OverLit val False _ ty) mb_neg _ -- Once that is settled, look for cases where the type of the -- entire overloaded literal matches the type of the underlying literal, -- and in that case take the short cut - -- NB: Watch out for wierd cases like Trac #3382 + -- NB: Watch out for weird cases like Trac #3382 -- f :: Int -> Int -- f "blah" = 4 -- which might be ok if we hvae 'instance IsString Int' diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index 53fed7274c..be052945aa 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -412,7 +412,7 @@ type CustomTermPrinter m = TermPrinterM m -> [Precedence -> Term -> (m (Maybe SDoc))] -- | Takes a list of custom printers with a explicit recursion knot and a term, --- and returns the output of the first succesful printer, or the default printer +-- and returns the output of the first successful printer, or the default printer cPprTerm :: Monad m => CustomTermPrinter m -> Term -> m SDoc cPprTerm printers_ = go 0 where printers = printers_ go diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 265f7f2e25..2d747b658c 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1006,7 +1006,7 @@ data ModGuts -- ^ Class instance environment from /home-package/ modules (including -- this one); c.f. 'tcg_inst_env' mg_fam_inst_env :: FamInstEnv, - -- ^ Type-family instance enviroment for /home-package/ modules + -- ^ Type-family instance environment for /home-package/ modules -- (including this one); c.f. 'tcg_fam_inst_env' mg_safe_haskell :: SafeHaskellMode, -- ^ Safe Haskell mode diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs index 5caf752e6d..97616baaf1 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs @@ -204,7 +204,7 @@ spillCost_chaitin spillCost_chaitin info graph reg -- Spilling a live range that only lives for 1 instruction - -- isn't going to help us at all - and we definately want to avoid + -- isn't going to help us at all - and we definitely want to avoid -- trying to re-spill previously inserted spill code. | lifetime <= 1 = 1/0 diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 63ee1f7d48..0b18597718 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -1600,7 +1600,7 @@ data PState = PState { -- This is the next token to be considered or, if it is Nothing, -- we need to get the next token from the input stream: alr_next_token :: Maybe (RealLocated Token), - -- This is what we consider to be the locatino of the last token + -- This is what we consider to be the location of the last token -- emitted: alr_last_loc :: RealSrcSpan, -- The stack of layout contexts: diff --git a/compiler/prelude/PrimOp.lhs b/compiler/prelude/PrimOp.lhs index 22753ee3ea..12f71c2230 100644 --- a/compiler/prelude/PrimOp.lhs +++ b/compiler/prelude/PrimOp.lhs @@ -292,7 +292,7 @@ Invariants: -- KSW: v, the second arg in parAt# and parAtForNow#, is used only to determine -- `the processor containing the expression v'; it is not evaluated -These primops are pretty wierd. +These primops are pretty weird. dataToTag# :: a -> Int (arg must be an evaluated data type) tagToEnum# :: Int -> a (result type must be an enumerated type) diff --git a/compiler/simplCore/OccurAnal.lhs b/compiler/simplCore/OccurAnal.lhs index d17b0561f5..6106388fa4 100644 --- a/compiler/simplCore/OccurAnal.lhs +++ b/compiler/simplCore/OccurAnal.lhs @@ -190,7 +190,7 @@ We put bindings {f = ef; g = eg } in a Rec group if "f uses g" and "g uses f", no matter how indirectly. We do a SCC analysis with an edge f -> g if "f uses g". -More precisely, "f uses g" iff g should be in scope whereever f is. +More precisely, "f uses g" iff g should be in scope wherever f is. That is, g is free in: a) the rhs 'ef' b) or the RHS of a rule for f (Note [Rules are extra RHSs]) diff --git a/compiler/specialise/Specialise.lhs b/compiler/specialise/Specialise.lhs index b83cecf03c..30224ba4fe 100644 --- a/compiler/specialise/Specialise.lhs +++ b/compiler/specialise/Specialise.lhs @@ -488,7 +488,7 @@ Some Ids have types like This seems curious at first, because we usually only have dictionary args whose types are of the form (C a) where a is a type variable. But this doesn't hold for the functions arising from instance decls, -which sometimes get arguements with types of form (C (T a)) for some +which sometimes get arguments with types of form (C (T a)) for some type constructor T. Should we specialise wrt this compound-type dictionary? We used to say diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index af36c7137b..d06b0579bd 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -577,7 +577,7 @@ newTyConInstRhs tycon tys Notes on type synonyms ~~~~~~~~~~~~~~~~~~~~~~ The various "split" functions (splitFunTy, splitRhoTy, splitForAllTy) try -to return type synonyms whereever possible. Thus +to return type synonyms wherever possible. Thus type Foo a = a -> a diff --git a/compiler/utils/Pretty.lhs b/compiler/utils/Pretty.lhs index 0c8e5fa1d0..39a78e1a69 100644 --- a/compiler/utils/Pretty.lhs +++ b/compiler/utils/Pretty.lhs @@ -71,7 +71,7 @@ Version 2.0 24 April 1997 nest k empty = empty which wasn't true before. - * Fixed an obscure bug in sep that occassionally gave very wierd behaviour + * Fixed an obscure bug in sep that occasionally gave very weird behaviour * Added $+$ diff --git a/compiler/vectorise/Vectorise/Monad/Local.hs b/compiler/vectorise/Vectorise/Monad/Local.hs index 5415c5691d..6816627fb9 100644 --- a/compiler/vectorise/Vectorise/Monad/Local.hs +++ b/compiler/vectorise/Vectorise/Monad/Local.hs @@ -34,7 +34,7 @@ readLEnv f = VM $ \_ genv lenv -> return (Yes genv lenv (f lenv)) setLEnv :: LocalEnv -> VM () setLEnv lenv = VM $ \_ genv _ -> return (Yes genv lenv ()) --- |Update the enviroment using the provided function. +-- |Update the environment using the provided function. -- updLEnv :: (LocalEnv -> LocalEnv) -> VM () updLEnv f = VM $ \_ genv lenv -> return (Yes genv (f lenv) ()) |