Reputation: 2814
This is a newbie question. Suppose I want to separate a list of files and directories into a list of files and a list of directories:
getFilesAndDirs :: [FilePath] -> ([FilePath], [FilePath])
getFilesAndDirs paths =
let ...
in (dirs, files)
Probably this is a hopeless duplicate, I just miss the right keywords. What is the right way to do (and call) this?
The files and the directories occur randomly.
Upvotes: 3
Views: 621
Reputation: 79
module SeparateFiles where
import Data.String
import System.FilePath.Posix
type Path = FilePath
getFilesAndDirs :: Path -> [(Path,Path)]
getFilesAndDirs path = [splitFileName path]
I understand that you want to split your FilePath extracting into a file and directory. I provide you a very short example.
Upvotes: 0
Reputation: 233327
You can use do
notation to orchestrate the impure parts of your program, and then use the built-in (pure) functions like partition
to do the actual work. Here's an example:
module Q47755054 (getFilesAndDirs) where
import Data.List (partition)
import Data.Bifunctor (bimap)
import System.Directory (doesDirectoryExist)
tagPath :: FilePath -> IO (FilePath, Bool)
tagPath path = do
isDirectory <- doesDirectoryExist path
return (path, isDirectory)
getFilesAndDirs :: [FilePath] -> IO ([FilePath], [FilePath])
getFilesAndDirs paths = do
taggedPaths <- mapM tagPath paths
return $ bimap (fmap fst) (fmap fst) $ partition snd taggedPaths
Notice that this uses the built-in mapM
function to get an impure list of values (IO [(FilePath, Bool)]
), but due to the do
syntax and the <-
binding, taggedPaths
'looks' like a pure value ([(FilePath, Bool)]
), and therefore you can pass it to partition
.
Notice, additionally, that tagPath
is just a module-level helper function that isn't exported by the module.
Upvotes: 2
Reputation: 477338
The Data.List
package has the partition :: (a -> Bool) -> [a] -> ([a],[a])
function which splits a list of a
s into a tuple of two lists of a
s based on a predicate.
The problem is however that when we check if a file is a directory, we probably will use isDirectory :: FilePath -> IO Bool
so we can not directly use this as a predicate (since IO Bool
is not equal to Bool
).
We can write our own partitionM
however, and use that one:
import Data.Bool(bool)
import Data.Foldable(foldrM)
partitionM :: (Foldable t, Monad m) => (a -> m Bool) -> t a -> m ([a], [a])
partitionM p = foldrM (selectM p) ([],[])
selectM :: Monad m => (a -> m Bool) -> a -> ([a], [a]) -> m ([a], [a])
selectM p x (ts,fs) = p x >>= return . bool (ts, x:fs) (x:ts,fs)
we can then use it like:
import System.Directory(isDirectory)
getFilesAndDirs :: [FilePath] -> IO ([FilePath], [FilePath])
getFilesAndDirs = partitionM isDirectory
Note that it is an IO ([FilePath], [FilePath])
, since we need to perform I/O to check if a path is indeed a directory (and not a file).
Upvotes: 2