[commit: packages/directory] master: Remove use of NondecreasingIndentation (ad2e0a1)

git at git.haskell.org git at git.haskell.org
Tue Apr 19 06:58:02 UTC 2016


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

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

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

commit ad2e0a110bf2ee2e2a3bd87963fa55505ca58b28
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Mon Apr 18 12:08:04 2016 -0400

    Remove use of NondecreasingIndentation


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

ad2e0a110bf2ee2e2a3bd87963fa55505ca58b28
 System/Directory.hs | 30 ++++++++++++++++--------------
 directory.cabal     |  1 -
 2 files changed, 16 insertions(+), 15 deletions(-)

diff --git a/System/Directory.hs b/System/Directory.hs
index ba09247..4e41e14 100644
--- a/System/Directory.hs
+++ b/System/Directory.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, NondecreasingIndentation #-}
+{-# LANGUAGE CPP #-}
 
 #if !(MIN_VERSION_base(4,8,0))
 -- In base-4.8.0 the Foreign module became Safe
@@ -250,10 +250,10 @@ The operation may fail with:
 -}
 
 getPermissions :: FilePath -> IO Permissions
-getPermissions name = do
+getPermissions name =
 #ifdef mingw32_HOST_OS
   -- issue #9: Windows doesn't like trailing path separators
-  withFilePath (dropTrailingPathSeparator name) $ \s -> do
+  withFilePath (dropTrailingPathSeparator name) $ \s ->
   -- stat() does a better job of guessing the permissions on Windows
   -- than access() does.  e.g. for execute permission, it looks at the
   -- filename extension :-)
@@ -276,6 +276,7 @@ getPermissions name = do
     }
    )
 #else
+  do
   read_ok  <- Posix.fileAccess name True  False False
   write_ok <- Posix.fileAccess name False True  False
   exec_ok  <- Posix.fileAccess name False False True
@@ -304,9 +305,9 @@ The operation may fail with:
 -}
 
 setPermissions :: FilePath -> Permissions -> IO ()
-setPermissions name (Permissions r w e s) = do
+setPermissions name (Permissions r w e s) =
 #ifdef mingw32_HOST_OS
-  allocaBytes sizeof_stat $ \ p_stat -> do
+  allocaBytes sizeof_stat $ \ p_stat ->
   withFilePath name $ \p_name -> do
     throwErrnoIfMinus1_ "setPermissions" $
       c_stat p_name p_stat
@@ -322,6 +323,7 @@ setPermissions name (Permissions r w e s) = do
    modifyBit False m b = m .&. (complement b)
    modifyBit True  m b = m .|. b
 #else
+  do
       stat <- Posix.getFileStatus name
       let mode = Posix.fileMode stat
       let mode1 = modifyBit r mode  Posix.ownerReadMode
@@ -340,15 +342,16 @@ foreign import ccall unsafe "_wchmod"
 #endif
 
 copyPermissions :: FilePath -> FilePath -> IO ()
-copyPermissions source dest = do
+copyPermissions source dest =
 #ifdef mingw32_HOST_OS
-  allocaBytes sizeof_stat $ \ p_stat -> do
-  withFilePath source $ \p_source -> do
+  allocaBytes sizeof_stat $ \ p_stat ->
+  withFilePath source $ \p_source ->
   withFilePath dest $ \p_dest -> do
     throwErrnoIfMinus1_ "copyPermissions" $ c_stat p_source p_stat
     mode <- st_mode p_stat
     throwErrnoIfMinus1_ "copyPermissions" $ c_wchmod p_dest mode
 #else
+  do
   stat <- Posix.getFileStatus source
   copyPermissionsFromStatus stat dest
 #endif
@@ -668,21 +671,20 @@ Either path refers to an existing non-directory object.
 -}
 
 renameDirectory :: FilePath -> FilePath -> IO ()
-renameDirectory opath npath = do
+renameDirectory opath npath =
    -- XXX this test isn't performed atomically with the following rename
 #ifdef mingw32_HOST_OS
    -- ToDo: use Win32 API
    withFileStatus "renameDirectory" opath $ \st -> do
    is_dir <- isDirectory st
 #else
+   do
    stat <- Posix.getFileStatus opath
    let is_dir = Posix.fileMode stat .&. Posix.directoryMode /= 0
 #endif
-   if (not is_dir)
-        then ioError (ioeSetErrorString
-                          (mkIOError InappropriateType "renameDirectory" Nothing (Just opath))
-                          "not a directory")
-        else do
+   when (not is_dir) $ do
+     ioError . (`ioeSetErrorString` "not a directory") $
+       (mkIOError InappropriateType "renameDirectory" Nothing (Just opath))
 #ifdef mingw32_HOST_OS
    Win32.moveFileEx opath npath Win32.mOVEFILE_REPLACE_EXISTING
 #else
diff --git a/directory.cabal b/directory.cabal
index d4d56da..a03cb67 100644
--- a/directory.cabal
+++ b/directory.cabal
@@ -38,7 +38,6 @@ Library
     default-language: Haskell2010
     other-extensions:
         CPP
-        NondecreasingIndentation
         Trustworthy
 
     exposed-modules:



More information about the ghc-commits mailing list