Re: [Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-21 Thread Bulat Ziganshin
Hello Steve,

Monday, December 19, 2005, 10:42:19 PM, you wrote:

SH> What I'm after is something like:
SH>  -- (psuedo-code)
SH>  [(b,c,d) |
SH>b <- getDirectoryContents a_dir,
SH>c <- getDirectoryContents (a_dir ++ "/" ++ b),
SH>d <- getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c) ],

this can't work because IO itself a monad, so "IO [a]" is two monads,
and you can iterate only over external one, which is IO. instead:

let foreach = flip mapM
list <- foreach (getDirectoryContents a_dir) $ \b ->
  foreach (getDirectoryContents (a_dir ++ "/" ++ b)) $ \c ->
foreach (getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c)) $ \d ->
  return (b,c,d)
return $ concatMap $ concatMap list


SH> This function isn't so clear at a glance, and yet what it's doing
SH> seems like a pretty common thing to want to do:  are there any library
SH> functions for monads (or IO in particular) that make this sort of thing
SH> easier, or should I to try and write my own function?  Looks not too
SH> difficult to write but I think I might miss something important if I didn't 
ask
SH> first...  How would you do it?

if you just need to find all files recursively - use library
http://hackage.haskell.org/packages/FilePath-0.1.0.tgz to manipulate
filenames and function `doesDirectoryExist` to check that it is a
directory. don't forget that `getDirectoryContents` returns list what
contains names "." and ".."

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-19 Thread Steve Harris
On 12/19/05, Chris Kuklewicz <[EMAIL PROTECTED]> wrote:
> Okay...that works.  Sweet.
>
> gdc x = ListT $ getDirectoryContents x
>
> get3levels top = runListT $ do
>   b <- gdc top
>   c <- gdc $ top++('/':b)
>   d <- gdc $ top++('/':b)++('/':c)
>   return (b,c,d)

Yeah, that's awesome: just as readable as the comprehension
psuedo-code if not more-so.  I knew some monad wizards would step out
with something nice.

Thanks for spelling out what Andrew was getting at also, it would have
been lost on me.  I haven't yet ventured into using any monads but IO
yet, maybe ListT would be a good place to start.


> I feel bound to point out http://haskell.org/hawiki/ListTDoneRight which
> has more to say about the details of ListT

OK. Thanks to you both Chris and Andrew.

Steve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-19 Thread Chris Kuklewicz
Okay...that works.  Sweet.

gdc x = ListT $ getDirectoryContents x

get3levels top = runListT $ do
  b <- gdc top
  c <- gdc $ top++('/':b)
  d <- gdc $ top++('/':b)++('/':c)
  return (b,c,d)

I feel bound to point out http://haskell.org/hawiki/ListTDoneRight which
has more to say about the details of ListT

Andrew Pimlott wrote:
> On Mon, Dec 19, 2005 at 01:42:19PM -0600, Steve Harris wrote:
> 
>>What I'm after is something like:
>> -- (psuedo-code)
>> [(b,c,d) |
>>   b <- getDirectoryContents a_dir,
>>   c <- getDirectoryContents (a_dir ++ "/" ++ b),
>>   d <- getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c) ],
> 
> 
> Check out Control.Monad.List.ListT, which combines list non-determinism
> with another monad.  Eg,
> 
> ListT (getDirectoryContents a_dir) :: ListT IO FilePath
> 
> Andrew
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-19 Thread Andrew Pimlott
On Mon, Dec 19, 2005 at 01:42:19PM -0600, Steve Harris wrote:
> What I'm after is something like:
>  -- (psuedo-code)
>  [(b,c,d) |
>b <- getDirectoryContents a_dir,
>c <- getDirectoryContents (a_dir ++ "/" ++ b),
>d <- getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c) ],

Check out Control.Monad.List.ListT, which combines list non-determinism
with another monad.  Eg,

ListT (getDirectoryContents a_dir) :: ListT IO FilePath

Andrew
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-19 Thread Chris Kuklewicz
Hmmm...I'll poke at it.

Steve Harris wrote:
> [reposted from haskell mailing list where I got no bites :) ]
> 
> Folks,
> I'm new to using monads, and I'd like some help improving a function
> definition that I wrote and which works, but for which I think there
> should be a clearer way to write it.
> 
> What I'm after is something like:
>  -- (psuedo-code)
>  [(b,c,d) |
>b <- getDirectoryContents a_dir,
>c <- getDirectoryContents (a_dir ++ "/" ++ b),
>d <- getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c) ],
> 
> 
> ie. where the generators feed from IO actions instead of lists,  but I
> gather this comprehension style isn't supported, which is too bad
> because it's really easy to read.  (Is this what was meant by "monad
> comprehensions" that I've heard reference to?)

Note: I will assume getDirectoryContents only returns directories.

You could write that only if you computed the directory contents first,
perhaps by loading them into nest maps or hashtables or simply lists.

The other problem is that you want a 3-tuple.  There are few generic
ways to create or select items in tuples.

Template haskell allows more generic code to construct and destruct
tuples.  It could define a version paramterised on the integer 3.

http://haskell.org/hawiki/TemplateHaskell
http://haskell.org/hawiki/TemplateHaskellTutorial

> 
> Here's how I actually wrote it, using nested folds:
> 
> import System.IO
> 
> -- Load directory entries 3 levels deep under a_dir, as list of tuples (b,c,d)
> 
> load3DirLevels :: FilePath -> IO [(String,String,String)]
>  load3DirLevels a_dir =
> do
>   bs <- getDirectoryContents a_dir
> 
> 
>  foldM (\tups b -> do
>cs <- getDirectoryContents (a_dir ++ "/" ++ b)
>foldM (\tups' c -> do
> ds <- getDirectoryContents (a_dir ++ "/" ++ b
> ++ "/" ++ c)
> foldM (\tups'' d -> do
>  return $ (b, c, d) : tups''
>   ) tups' ds
>  ) tups cs
> ) [] bs
> 
> This function isn't so clear at a glance, and yet what it's doing
> seems like a pretty common thing to want to do:  are there any library
> functions for monads (or IO in particular) that make this sort of thing
> easier, or should I to try and write my own function?  Looks not too
> difficult to write but I think I might miss something important if I didn't 
> ask
> first...  How would you do it?

The foldM code, given your pseudo-code as a comment above, is clear.
Perhaps this can be made simpler by making it more generic.  Somewhat
tested:

import Control.Monad (liftM)
getDirectoryContents _ = return ["a","b","c"]

glue :: String -> [String] -> String
glue sep values = foldr1 (\a b-> a ++ sep ++ b) values

descend :: Int -> [String] -> IO [[String]]
descend n _ | n < 0 = fail "Cannot descend negative levels"
descend 0 vs = return [vs]
descend n vs = do
  let path = glue "/" vs
  deeper <- getDirectoryContents path
  liftM concat (mapM (\v' -> descend (n-1) (vs++[v'])) deeper)

listTo3Tuple [top,a,b,c] = (a,b,c)
listTo3Tuple _ = error "malformed list"

load3DirLevels top = liftM (map listTo3Tuple) (descend 3 [top])

The descend function does the foldM work recursively with a counter,
returning a list of lists of path components.  Then the tuple is formed.

Usually when I use a counter, someone else comes back with a more clever
implicit definition, so I'll do that myself:

goDeeper :: [[String]] -> IO [[String]]
goDeeper []  = return []
goDeeper (vs:vss) = do
  let path = glue "/" vs
  deeper <- getDirectoryContents path
  liftM (([ (vs++[v']) | v'<- deeper ]) ++) (goDeeper vss)

load3DirLevels' a_dir = liftM (map listTo3Tuple) (goDeeper [[a_dir]] >>=
goDeeper >>= goDeeper)

which seems to work
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] comprehension generators from IO [a]'s ?

2005-12-19 Thread Steve Harris
[reposted from haskell mailing list where I got no bites :) ]

Folks,
I'm new to using monads, and I'd like some help improving a function
definition that I wrote and which works, but for which I think there
should be a clearer way to write it.

What I'm after is something like:
 -- (psuedo-code)
 [(b,c,d) |
   b <- getDirectoryContents a_dir,
   c <- getDirectoryContents (a_dir ++ "/" ++ b),
   d <- getDirectoryContents (a_dir ++ "/" ++ b ++ "/" ++ c) ],


ie. where the generators feed from IO actions instead of lists,  but I
gather this comprehension style isn't supported, which is too bad
because it's really easy to read.  (Is this what was meant by "monad
comprehensions" that I've heard reference to?)

Here's how I actually wrote it, using nested folds:

import System.IO

-- Load directory entries 3 levels deep under a_dir, as list of tuples (b,c,d)

load3DirLevels :: FilePath -> IO [(String,String,String)]
 load3DirLevels a_dir =
do
  bs <- getDirectoryContents a_dir


 foldM (\tups b -> do
   cs <- getDirectoryContents (a_dir ++ "/" ++ b)
   foldM (\tups' c -> do
ds <- getDirectoryContents (a_dir ++ "/" ++ b
++ "/" ++ c)
foldM (\tups'' d -> do
 return $ (b, c, d) : tups''
  ) tups' ds
 ) tups cs
) [] bs

This function isn't so clear at a glance, and yet what it's doing
seems like a pretty common thing to want to do:  are there any library
functions for monads (or IO in particular) that make this sort of thing
easier, or should I to try and write my own function?  Looks not too
difficult to write but I think I might miss something important if I didn't ask
first...  How would you do it?

Thanks
Steve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe