[commit: packages/directory] master: Rename getDirectoryContentsA to listDirectory (91062ae)

git at git.haskell.org git at git.haskell.org
Fri Dec 18 09:53:05 UTC 2015


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

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

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

commit 91062ae0aab4fc3c7ca7e725912fc46833e9681c
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Sat Oct 10 20:29:20 2015 -0400

    Rename getDirectoryContentsA to listDirectory
    
    Rationale:
    
      - Name is shorter and more familiar (most users don't need
        getDirectoryContents).
      - The 'A' suffix doesn't really fit within the existing conventions,
        nor is it clear what it means.


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

91062ae0aab4fc3c7ca7e725912fc46833e9681c
 System/Directory.hs           | 12 ++++++------
 changelog.md                  |  3 ++-
 tests/CopyFile001.hs          |  4 ++--
 tests/CopyFile002.hs          |  4 ++--
 tests/GetDirContents001.hs    |  4 ++--
 tests/TestUtils.hs            |  2 +-
 tests/WithCurrentDirectory.hs |  4 ++--
 7 files changed, 17 insertions(+), 16 deletions(-)

diff --git a/System/Directory.hs b/System/Directory.hs
index 8f4dc36..511b7c4 100644
--- a/System/Directory.hs
+++ b/System/Directory.hs
@@ -29,7 +29,7 @@ module System.Directory
     , removeDirectory
     , removeDirectoryRecursive
     , renameDirectory
-    , getDirectoryContentsA
+    , listDirectory
     , getDirectoryContents
     -- ** Current working directory
     , getCurrentDirectory
@@ -572,7 +572,7 @@ removePathRecursive path =
 removeContentsRecursive :: FilePath -> IO ()
 removeContentsRecursive path =
   (`ioeSetLocation` "removeContentsRecursive") `modifyIOError` do
-    cont <- getDirectoryContentsA path
+    cont <- listDirectory path
     mapM_ removePathRecursive [path </> x | x <- cont]
     removeDirectory path
 
@@ -964,7 +964,7 @@ findFilesWith f (d:ds) fileName = do
         else findFilesWith f ds fileName
 
 #ifdef __GLASGOW_HASKELL__
--- | Similar to 'getDirectoryContentsA', but always includes the special entries (@.@
+-- | Similar to 'listDirectory', but always includes the special entries (@.@
 -- and @..@).  (This applies to Windows as well.)
 getDirectoryContents :: FilePath -> IO [FilePath]
 getDirectoryContents path =
@@ -1002,7 +1002,7 @@ getDirectoryContents path =
                  -- no need to reverse, ordering is undefined
 #endif /* mingw32 */
 
--- | @'getDirectoryContentsA' dir@ returns a list of /all/ entries in /dir/ without
+-- | @'listDirectory' dir@ returns a list of /all/ entries in /dir/ without
 -- the special entries (@.@ and @..@).
 --
 -- The operation may fail with:
@@ -1033,8 +1033,8 @@ getDirectoryContents path =
 --
 -- @since 1.2.5.0
 --
-getDirectoryContentsA :: FilePath -> IO [FilePath]
-getDirectoryContentsA path =
+listDirectory :: FilePath -> IO [FilePath]
+listDirectory path =
   (filter f) <$> (getDirectoryContents path)
   where f filename = filename /= "." && filename /= ".."
 
diff --git a/changelog.md b/changelog.md
index 7a2e36d..8b90f78 100644
--- a/changelog.md
+++ b/changelog.md
@@ -3,7 +3,8 @@ Changelog for the [`directory`][1] package
 
 ## 1.2.5.0 (October 2015)
 
-  * Add `getDirectoryContentsA`, which leaves out `.` and `..`
+  * Add `listDirectory`, which is similar to `getDirectoryContents` but leaves
+    out `.` and `..`
     ([#36](https://github.com/haskell/directory/pull/36))
 
 ## 1.2.4.0 (September 2015)
diff --git a/tests/CopyFile001.hs b/tests/CopyFile001.hs
index 6ecb706..55df9ce 100644
--- a/tests/CopyFile001.hs
+++ b/tests/CopyFile001.hs
@@ -9,9 +9,9 @@ main :: TestEnv -> IO ()
 main _t = do
   createDirectory dir
   writeFile (dir </> from) contents
-  T(expectEq) () [from] . sort =<< getDirectoryContentsA dir
+  T(expectEq) () [from] . sort =<< listDirectory dir
   copyFile (dir </> from) (dir </> to)
-  T(expectEq) () [from, to] . sort =<< getDirectoryContentsA dir
+  T(expectEq) () [from, to] . sort =<< listDirectory dir
   T(expectEq) () contents =<< readFile (dir </> to)
   where
     contents = "This is the data\n"
diff --git a/tests/CopyFile002.hs b/tests/CopyFile002.hs
index ea2cd36..66bd64a 100644
--- a/tests/CopyFile002.hs
+++ b/tests/CopyFile002.hs
@@ -9,9 +9,9 @@ main _t = do
   -- Similar to CopyFile001 but moves a file in the current directory
   -- (Bug #1652 on GHC Trac)
   writeFile from contents
-  T(expectEq) () [from] . sort =<< getDirectoryContentsA "."
+  T(expectEq) () [from] . sort =<< listDirectory "."
   copyFile from to
-  T(expectEq) () [from, to] . sort =<< getDirectoryContentsA "."
+  T(expectEq) () [from, to] . sort =<< listDirectory "."
   T(expectEq) () contents =<< readFile to
   where
     contents = "This is the data\n"
diff --git a/tests/GetDirContents001.hs b/tests/GetDirContents001.hs
index 768d79a..b70104b 100644
--- a/tests/GetDirContents001.hs
+++ b/tests/GetDirContents001.hs
@@ -11,12 +11,12 @@ main :: TestEnv -> IO ()
 main _t = do
   createDirectory dir
   T(expectEq) () specials . sort =<< getDirectoryContents dir
-  T(expectEq) () [] . sort =<< getDirectoryContentsA dir
+  T(expectEq) () [] . sort =<< listDirectory dir
   names <- for [1 .. 100 :: Int] $ \ i -> do
     let name = 'f' : show i
     writeFile (dir </> name) ""
     return name
   T(expectEq) () (sort (specials <> names)) . sort =<< getDirectoryContents dir
-  T(expectEq) () (sort names) . sort =<< getDirectoryContentsA dir
+  T(expectEq) () (sort names) . sort =<< listDirectory dir
   where dir      = "dir"
         specials = [".", ".."]
diff --git a/tests/TestUtils.hs b/tests/TestUtils.hs
index 11a8ea8..b04cbb0 100644
--- a/tests/TestUtils.hs
+++ b/tests/TestUtils.hs
@@ -41,7 +41,7 @@ copyPathRecursive source dest =
     dirExists <- doesDirectoryExist source
     if dirExists
       then do
-        contents <- getDirectoryContentsA source
+        contents <- listDirectory source
         createDirectory dest
         mapM_ (uncurry copyPathRecursive)
           [(source </> x, dest </> x) | x <- contents]
diff --git a/tests/WithCurrentDirectory.hs b/tests/WithCurrentDirectory.hs
index 7389f6c..2f9c04a 100644
--- a/tests/WithCurrentDirectory.hs
+++ b/tests/WithCurrentDirectory.hs
@@ -9,13 +9,13 @@ main :: TestEnv -> IO ()
 main _t = do
   createDirectory dir
   -- Make sure we're starting empty
-  T(expectEq) () [] . sort =<< getDirectoryContentsA dir
+  T(expectEq) () [] . sort =<< listDirectory dir
   cwd <- getCurrentDirectory
   withCurrentDirectory dir (writeFile testfile contents)
   -- Are we still in original directory?
   T(expectEq) () cwd =<< getCurrentDirectory
   -- Did the test file get created?
-  T(expectEq) () [testfile] . sort =<< getDirectoryContentsA dir
+  T(expectEq) () [testfile] . sort =<< listDirectory dir
   -- Does the file contain what we expected to write?
   T(expectEq) () contents =<< readFile (dir </> testfile)
   where



More information about the ghc-commits mailing list