
Hi all, I have a list of entries for a directory (FilePaths) and I'd like to partition them into files and directories using Data.List.partition: partition :: [a] -> ([a], [a]) Now, one solution is to use unsafePerformIO: splitDirFile :: [FilePath] -> ([FilePath], [FilePath]) splitDirFile paths = do partition (\p -> unsafePerformIO (doesDirectoryExist p)) paths Two questions: a) Is it possible to do this without invoking unsafePerformIO? Ie with a function signature of say: partition :: [FilePath] -> IO ([FilePath], [FilePath]) b) Exactly how unsafe is the unsafePerformIO version? Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- The main confusion about C++ is that its practitioners think it is simultaneously a high and low level language when in reality it is good at neither.

Hi Erik,The short answer to your question is to not write splitDirFile to
operate on FilePaths, but on some wrapper around FilePaths that also contain
information about whether each path is to a directory or a file. Then you
can call splitDirFile purely. For the long, but very good, answer, see RWH,
where they discuss this very specifically:
http://book.realworldhaskell.org/read/io-case-study-a-library-for-searching-...
On Tue, Jan 27, 2009 at 11:07 PM, Erik de Castro Lopo
wrote:
Hi all,
I have a list of entries for a directory (FilePaths) and I'd like to partition them into files and directories using Data.List.partition:
partition :: [a] -> ([a], [a])
Now, one solution is to use unsafePerformIO:
splitDirFile :: [FilePath] -> ([FilePath], [FilePath]) splitDirFile paths = do partition (\p -> unsafePerformIO (doesDirectoryExist p)) paths
Two questions:
a) Is it possible to do this without invoking unsafePerformIO? Ie with a function signature of say:
partition :: [FilePath] -> IO ([FilePath], [FilePath])
b) Exactly how unsafe is the unsafePerformIO version?
Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- The main confusion about C++ is that its practitioners think it is simultaneously a high and low level language when in reality it is good at neither. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

You can do (something like; this is untested)
splitDirFile :: [FilePath] -> IO ([FilePath],[FilePath])
splitDirFile [] = return ([],[])
splitDirFile (f:fs) = do
(yess,nos) <- splitDirFile fs
exists <- doesDirectoryExist f
return $ if exists
then (f:yess,nos)
else (yess,f:nos)
You might also look at Control.Monad.filterM. I often define a
function "partitionM" which is like partition except it uses a monadic
test, just like you have.
Alex
On Tue, Jan 27, 2009 at 8:07 PM, Erik de Castro Lopo
Hi all,
I have a list of entries for a directory (FilePaths) and I'd like to partition them into files and directories using Data.List.partition:
partition :: [a] -> ([a], [a])
Now, one solution is to use unsafePerformIO:
splitDirFile :: [FilePath] -> ([FilePath], [FilePath]) splitDirFile paths = do partition (\p -> unsafePerformIO (doesDirectoryExist p)) paths
Two questions:
a) Is it possible to do this without invoking unsafePerformIO? Ie with a function signature of say:
partition :: [FilePath] -> IO ([FilePath], [FilePath])
b) Exactly how unsafe is the unsafePerformIO version?
Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- The main confusion about C++ is that its practitioners think it is simultaneously a high and low level language when in reality it is good at neither. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Alexander Dunlap wrote:
You can do (something like; this is untested)
splitDirFile :: [FilePath] -> IO ([FilePath],[FilePath]) splitDirFile [] = return ([],[]) splitDirFile (f:fs) = do (yess,nos) <- splitDirFile fs exists <- doesDirectoryExist f return $ if exists then (f:yess,nos) else (yess,f:nos)
Untested, but seems to work perfectly :-). Thanks. However, that brings me to the next stage where again I'm trapped. I would like to do a foldl' on a function that returns IO [FilePath]. I tried using Control.Monad.foldM, but then I end up with a function taht return : IO (IO ([FilePath])) which doesn't work :-). It seems pretty obvious that I could implement a recursion like Alexander did above for splitDirFile but I was wondering if there was a more general solution. Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- Heisenbugs - The bugs that go away when you turn on debugging.

On Wed, Jan 28, 2009 at 5:18 PM, Erik de Castro Lopo
Alexander Dunlap wrote:
You can do (something like; this is untested)
splitDirFile :: [FilePath] -> IO ([FilePath],[FilePath]) splitDirFile [] = return ([],[]) splitDirFile (f:fs) = do (yess,nos) <- splitDirFile fs exists <- doesDirectoryExist f return $ if exists then (f:yess,nos) else (yess,f:nos)
Untested, but seems to work perfectly :-). Thanks.
However, that brings me to the next stage where again I'm trapped. I would like to do a foldl' on a function that returns IO [FilePath].
I tried using Control.Monad.foldM, but then I end up with a function taht return :
IO (IO ([FilePath]))
which doesn't work :-).
It seems pretty obvious that I could implement a recursion like Alexander did above for splitDirFile but I was wondering if there was a more general solution.
Cheers, Erik
It seems like foldM ought to do what you want. Could you post some more details please? Alex

Alexander Dunlap wrote:
It seems like foldM ought to do what you want. Could you post some more details please?
This is a function that I have working in Ocaml which is a little more lenient about IO :-). This is what I have but won't compile: fileNames :: ([FilePath] -> FilePath -> FilePath -> [FilePath]) -> [FilePath] -> FilePath -> IO [FilePath] fileNames builder builder_accum topdir = do names <- getDirectoryContents topdir let properNames = filter (`notElem` [".", ".."]) names (dirs, files) <- splitDirFile properNames let accum <- foldl' (\ acc f -> builder acc topdir f) builder_accum files return $ foldM (\ acc d -> fileNames builder accum (topdir > d)) accum dirs I get following error on the foldM: Couldn't match expected type `[FilePath]' against inferred type `IO [FilePath]' Expected type: IO [FilePath] Inferred type: IO (IO [FilePath]) Thinking about it some more, I can see the problem; accum is an "IO [FilePath]" and my builder function requires a "[FilePath]". Once I get the function working I would like to generalize it to: fileNames :: (a -> FilePath -> FilePath -> a) -> a -> FilePath -> IO a Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "Re graphics: A picture is worth 10K words - but only those to describe the picture. Hardly any sets of 10K words can be adequately described with pictures." -- Alan Perlis

On Wed, Jan 28, 2009 at 6:14 PM, Erik de Castro Lopo
Alexander Dunlap wrote:
It seems like foldM ought to do what you want. Could you post some more details please?
This is a function that I have working in Ocaml which is a little more lenient about IO :-).
This is what I have but won't compile:
fileNames :: ([FilePath] -> FilePath -> FilePath -> [FilePath]) -> [FilePath] -> FilePath -> IO [FilePath] fileNames builder builder_accum topdir = do names <- getDirectoryContents topdir let properNames = filter (`notElem` [".", ".."]) names (dirs, files) <- splitDirFile properNames let accum <- foldl' (\ acc f -> builder acc topdir f) builder_accum files return $ foldM (\ acc d -> fileNames builder accum (topdir > d)) accum dirs
I get following error on the foldM:
Couldn't match expected type `[FilePath]' against inferred type `IO [FilePath]' Expected type: IO [FilePath] Inferred type: IO (IO [FilePath])
Thinking about it some more, I can see the problem; accum is an "IO [FilePath]" and my builder function requires a "[FilePath]".
Once I get the function working I would like to generalize it to:
fileNames :: (a -> FilePath -> FilePath -> a) -> a -> FilePath -> IO a
Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo
Try removing the "return $" on the last line. foldM ... will already be in the IO monad; return will lift the IO a into the IO monad again, so you'll have IO (IO a), which you don't want. Alex

Alexander Dunlap wrote:
Try removing the "return $" on the last line. foldM ... will already be in the IO monad; return will lift the IO a into the IO monad again, so you'll have IO (IO a), which you don't want.
Fantastic! Worked a treat. Thanks, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "C++ has its place in the history of programming languages. Just as Caligula has his place in the history of the Roman Empire." -- Robert Firth

Alexander Dunlap wrote:
You might also look at Control.Monad.filterM. I often define a function "partitionM" which is like partition except it uses a monadic test, just like you have.
Just for completeness, my partitionM: partitionM :: (Monad m) => (a -> m Bool) -> [a] -> m ([a], [a]) partitionM _ [] = return ([], []) partitionM p (x:xs) = do flg <- p x (ys, ns) <- partitionM p xs return (if flg then (x:ys, ns) else (ys, x:ns)) Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "Indeed, I am impressed that Google runs an 8,000 node Linux cluster, 5 data centers, an extensive network, and a rapidly evolving application all with a staff of 12." -- http://research.microsoft.com/~gray/papers/FAAMs_HPTS.doc

Alexander Dunlap wrote:
You can do (something like; this is untested)
splitDirFile :: [FilePath] -> IO ([FilePath],[FilePath]) splitDirFile [] = return ([],[]) splitDirFile (f:fs) = do (yess,nos) <- splitDirFile fs exists <- doesDirectoryExist f return $ if exists then (f:yess,nos) else (yess,f:nos)
You might also look at Control.Monad.filterM. I often define a function "partitionM" which is like partition except it uses a monadic test, just like you have.
How about splitDirFile ps = ((map fst *** map fst) . partition snd . zip ps) `liftM` mapM doesDirectoryExist ps There is no need to rewrite partition , you can reuse it. Hm, the plumbing seems slightly cumbersome to me, maybe Conal's editor combinators http://conal.net/blog/posts/semantic-editor-combinators/ can help. Regards, apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Alexander Dunlap
-
Andrew Wagner
-
Erik de Castro Lopo
-
Heinrich Apfelmus