[commit: ghc] master: Fix typos (9b3d4cd)

Gabor Greif ggreif at gmail.com
Sat Apr 6 11:53:14 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

https://github.com/ghc/ghc/commit/9b3d4cdd26a9fbf0a1183185bedbe11925b1ddb4

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

commit 9b3d4cdd26a9fbf0a1183185bedbe11925b1ddb4
Author: Gabor Greif <ggreif at gmail.com>
Date:   Fri Apr 5 20:22:35 2013 +0200

    Fix typos

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

 compiler/cmm/CmmPipeline.hs                          | 6 +++---
 compiler/coreSyn/CoreUnfold.lhs                      | 2 +-
 compiler/nativeGen/RegAlloc/Linear/Base.hs           | 2 +-
 compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs   | 2 +-
 compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs | 2 +-
 compiler/utils/Stream.hs                             | 4 ++--
 docs/comm/rts-libs/prelude.html                      | 4 ++--
 7 files changed, 11 insertions(+), 11 deletions(-)

diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs
index 6093419..78fed22 100644
--- a/compiler/cmm/CmmPipeline.hs
+++ b/compiler/cmm/CmmPipeline.hs
@@ -62,7 +62,7 @@ cpsTop hsc_env proc =
        --
        CmmProc h l v g <- {-# SCC "cmmCfgOpts(1)" #-}
             return $ cmmCfgOptsProc splitting_proc_points proc
-       dump Opt_D_dump_cmm_cfg "Post control-flow optimsations" g
+       dump Opt_D_dump_cmm_cfg "Post control-flow optimisations" g
 
        let !TopInfo {stack_info=StackInfo { arg_space = entry_off
                                           , do_layout = do_layout }} = h
@@ -135,7 +135,7 @@ cpsTop hsc_env proc =
                              else gs
             gs <- return (map removeUnreachableBlocksProc gs)
                 -- Note [unreachable blocks]
-            dumps Opt_D_dump_cmm_cfg "Post control-flow optimsations" gs
+            dumps Opt_D_dump_cmm_cfg "Post control-flow optimisations" gs
 
             return (cafEnv, gs)
 
@@ -155,7 +155,7 @@ cpsTop hsc_env proc =
                              else g
             g <- return (removeUnreachableBlocksProc g)
                 -- Note [unreachable blocks]
-            dump' Opt_D_dump_cmm_cfg "Post control-flow optimsations" g
+            dump' Opt_D_dump_cmm_cfg "Post control-flow optimisations" g
 
             return (cafEnv, [g])
 
diff --git a/compiler/coreSyn/CoreUnfold.lhs b/compiler/coreSyn/CoreUnfold.lhs
index 65235a6..d49717c 100644
--- a/compiler/coreSyn/CoreUnfold.lhs
+++ b/compiler/coreSyn/CoreUnfold.lhs
@@ -665,7 +665,7 @@ Literal integers *can* be big (mkInteger [...coefficients...]), but
 need not be (S# n).  We just use an aribitrary big-ish constant here
 so that, in particular, we don't inline top-level defns like
    n = S# 5
-There's no point in doing so -- any optimsations will see the S#
+There's no point in doing so -- any optimisations will see the S#
 through n's unfolding.  Nor will a big size inhibit unfoldings functions
 that mention a literal Integer, because the float-out pass will float
 all those constants to top level.
diff --git a/compiler/nativeGen/RegAlloc/Linear/Base.hs b/compiler/nativeGen/RegAlloc/Linear/Base.hs
index e583313..d4f124e 100644
--- a/compiler/nativeGen/RegAlloc/Linear/Base.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/Base.hs
@@ -99,7 +99,7 @@ data RegAllocStats
         { ra_spillInstrs        :: UniqFM [Int] }
 
 
--- | The register alloctor state
+-- | The register allocator state
 data RA_State freeRegs
         = RA_State
 
diff --git a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
index 333cf75..0bdb49f 100644
--- a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
@@ -42,7 +42,7 @@ releaseReg _ _
 initFreeRegs :: Platform -> FreeRegs
 initFreeRegs platform = foldr releaseReg noFreeRegs (allocatableRegs platform)
 
-getFreeRegs :: RegClass -> FreeRegs -> [RealReg]        -- lazilly
+getFreeRegs :: RegClass -> FreeRegs -> [RealReg]        -- lazily
 getFreeRegs cls (FreeRegs g f)
     | RcDouble <- cls = go f (0x80000000) 63
     | RcInteger <- cls = go g (0x80000000) 31
diff --git a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
index f8f3c92..6b6e67c 100644
--- a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
@@ -50,7 +50,7 @@ initFreeRegs platform
 
                         
 -- | Get all the free registers of this class.
-getFreeRegs :: RegClass -> FreeRegs -> [RealReg]        -- lazilly
+getFreeRegs :: RegClass -> FreeRegs -> [RealReg]        -- lazily
 getFreeRegs cls (FreeRegs g f d)
         | RcInteger <- cls = map RealRegSingle                  $ go 1 g 1 0  
         | RcFloat   <- cls = map RealRegSingle                  $ go 1 f 1 32 
diff --git a/compiler/utils/Stream.hs b/compiler/utils/Stream.hs
index 2fa76d2..bfc6f93 100644
--- a/compiler/utils/Stream.hs
+++ b/compiler/utils/Stream.hs
@@ -66,7 +66,7 @@ collect str = go str []
 fromList :: Monad m => [a] -> Stream m a ()
 fromList = mapM_ yield
 
--- | Apply a function to each element of a 'Stream', lazilly
+-- | Apply a function to each element of a 'Stream', lazily
 map :: Monad m => (a -> b) -> Stream m a x -> Stream m b x
 map f str = Stream $ do
    r <- runStream str
@@ -74,7 +74,7 @@ map f str = Stream $ do
      Left x -> return (Left x)
      Right (a, str') -> return (Right (f a, Stream.map f str'))
 
--- | Apply a monadic operation to each element of a 'Stream', lazilly
+-- | Apply a monadic operation to each element of a 'Stream', lazily
 mapM :: Monad m => (a -> m b) -> Stream m a x -> Stream m b x
 mapM f str = Stream $ do
    r <- runStream str
diff --git a/docs/comm/rts-libs/prelude.html b/docs/comm/rts-libs/prelude.html
index 4ad6c20..c93e90d 100644
--- a/docs/comm/rts-libs/prelude.html
+++ b/docs/comm/rts-libs/prelude.html
@@ -8,7 +8,7 @@
   <body BGCOLOR="FFFFFF">
     <h1>The GHC Commentary - Cunning Prelude Code</h1>
     <p>
-      GHC's uses a many optimsations and GHC specific techniques (unboxed
+      GHC's uses a many optimisations and GHC specific techniques (unboxed
       values, RULES pragmas, and so on) to make the heavily used Prelude code
       as fast as possible.
 
@@ -106,7 +106,7 @@ mapList f (x:xs) = f x : mapList f xs
       foldr/build rules, and if no foldr/build rule matches, the "mapList"
       rule <em>closes</em> it again in a later phase of optimisation - after
       build was inlined.  As a consequence, the whole thing depends a bit on
-      the timing of the various optimsations (the map might be closed again
+      the timing of the various optimisations (the map might be closed again
       before any of the foldr/build rules fires).  To make the timing
       deterministic, <code>build</code> gets a <code>{-# INLINE 2 build
       #-}</code> pragma, which delays <code>build</code>'s inlining, and thus,





More information about the ghc-commits mailing list