Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Extra directory functions. Most of these functions provide cleaned up and generalised versions
of getDirectoryContents
, see listContents
for the differences.
- module System.Directory
- withCurrentDirectory :: FilePath -> IO a -> IO a
- createDirectoryPrivate :: String -> IO ()
- listContents :: FilePath -> IO [FilePath]
- listFiles :: FilePath -> IO [FilePath]
- listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath]
- listFilesRecursive :: FilePath -> IO [FilePath]
Documentation
module System.Directory
withCurrentDirectory :: FilePath -> IO a -> IO a Source
Set the current directory, perform an operation, then change back. Remember that the current directory is a global variable, so calling this function multithreaded is almost certain to go wrong. Avoid changing the current directory if you can.
withTempDir $ \dir -> do writeFile (dir </> "foo.txt") ""; withCurrentDirectory dir $ doesFileExist "foo.txt"
createDirectoryPrivate :: String -> IO () Source
Create a directory with permissions so that only the current user can view it.
On Windows this function is equivalent to createDirectory
.
listContents :: FilePath -> IO [FilePath] Source
List the files and directories directly within a directory.
Each result will be prefixed by the query directory, and the special directories .
and ..
will be ignored.
Intended as a cleaned up version of getDirectoryContents
.
withTempDir $ \dir -> do writeFile (dir </> "test.txt") ""; (== [dir </> "test.txt"]) <$> listContents dir let touch = mapM_ $ \x -> createDirectoryIfMissing True (takeDirectory x) >> writeFile x "" let listTest op as bs = withTempDir $ \dir -> do touch $ map (dir </>) as; res <- op dir; return $ map (drop (length dir + 1)) res == bs listTest listContents ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","foo","zoo"]
listFiles :: FilePath -> IO [FilePath] Source
Like listContents
, but only returns the files in a directory, not other directories.
Each file will be prefixed by the query directory.
listTest listFiles ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","zoo"]
listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath] Source
Like listFilesRecursive
, but with a predicate to decide where to recurse into.
Typically directories starting with .
would be ignored. The initial argument directory
will have the test applied to it.
listTest (listFilesInside $ return . not . isPrefixOf "." . takeFileName) ["bar.txt","foo" </> "baz.txt",".foo" </> "baz2.txt", "zoo"] ["bar.txt","zoo","foo" </> "baz.txt"] listTest (listFilesInside $ const $ return False) ["bar.txt"] []
listFilesRecursive :: FilePath -> IO [FilePath] Source
Like listFiles
, but goes recursively through all subdirectories.
This function will follow symlinks, and if they form a loop, this function will not terminate.
listTest listFilesRecursive ["bar.txt","zoo","foo" </> "baz.txt"] ["bar.txt","zoo","foo" </> "baz.txt"]