[commit: ghc] master: Avoid trivial cases of NondecreasingIndentation (e199891)

git at git.haskell.org git at git.haskell.org
Thu May 15 08:33:08 UTC 2014


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

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

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

commit e199891f199795468cdcf977d5395d3c846cad72
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu May 15 09:51:51 2014 +0200

    Avoid trivial cases of NondecreasingIndentation
    
    This cleanup allows the following refactoring commit to avoid adding a
    few `{-# LANGUAGE NondecreasingIndentation #-}` pragmas.
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

e199891f199795468cdcf977d5395d3c846cad72
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 4 ++--
 compiler/main/HeaderInfo.hs             | 4 ++--
 compiler/utils/Binary.hs                | 7 +++----
 3 files changed, 7 insertions(+), 8 deletions(-)

diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index 808c591..1140145 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -1002,8 +1002,8 @@ genMachOp _ op [x] = case op of
         sameConv from ty reduce expand = do
             x'@(vx, stmts, top) <- exprToVar x
             let sameConv' op = do
-                (v1, s1) <- doExpr ty $ Cast op vx ty
-                return (v1, stmts `snocOL` s1, top)
+                    (v1, s1) <- doExpr ty $ Cast op vx ty
+                    return (v1, stmts `snocOL` s1, top)
             dflags <- getDynFlags
             let toWidth = llvmWidthInBits dflags ty
             -- LLVM doesn't like trying to convert to same width, so
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index a083f4f..3e1edc3 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -185,8 +185,8 @@ lazyGetToks dflags filename handle = do
        -- large module names (#5981)
      nextbuf <- hGetStringBufferBlock handle new_size
      if (len nextbuf == 0) then lazyLexBuf handle state True new_size else do
-     newbuf <- appendStringBuffers (buffer state) nextbuf
-     unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size
+       newbuf <- appendStringBuffers (buffer state) nextbuf
+       unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size
 
 
 getToks :: DynFlags -> FilePath -> StringBuffer -> [Located Token]
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index 332bfc8..e9b7123 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -707,14 +707,13 @@ getBS bh = do
   l <- get bh
   fp <- mallocForeignPtrBytes l
   withForeignPtr fp $ \ptr -> do
-  let
-        go n | n == l = return $ BS.fromForeignPtr fp 0 l
+    let go n | n == l = return $ BS.fromForeignPtr fp 0 l
              | otherwise = do
                 b <- getByte bh
                 pokeElemOff ptr n b
                 go (n+1)
-  --
-  go 0
+    --
+    go 0
 
 instance Binary ByteString where
   put_ bh f = putBS bh f



More information about the ghc-commits mailing list