Re: erreta, a couple of unimportant missing words :-(

2002-11-20 Thread Ahn Ki-yung
Ahn Ki-yung wrote:

Simple Cat (revisitied)

\begin{code}

import IO

findM f [] = return Nothing
findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs }

isLeft (Left _) = True
isLeft _ = False

main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

\end{code}

This is my answer for the question of my own,

which is posted a couple
  

of days before.

There are mapM, filterM in the Haskell 98 Standard Library.

But why no findM there ?

As you can see from simple cat, it seems quite useful.

I think fildM should be added to the module Monad.

  



-- 
Ahn Ki-yung



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Simple Cat (revisitied)

\begin{code}

import IO

findM f [] = return Nothing
findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs }

isLeft (Left _) = True
isLeft _ = False

main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

\end{code}

This is my answer for the question of my own,

which is posted a couple

There are mapM, filterM in the Haskell 98 Standard Library.

But why no findM there ?

As you can see from simple cat, it seems quite useful.

I think fildM should be added to the module Monad.

-- 
Ahn Ki-yung


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Jorge Adriano

 Simple Cat (revisitied)

 \begin{code}

 import IO

 findM f [] = return Nothing
 findM f (x:xs) = do { v - x; if f v then return (Just v) else findM f xs }

 isLeft (Left _) = True
 isLeft _ = False

 main = findM (isLeft) (hCat stdin) where hCat h = try (hGetLine h) : hCat h

 \end{code}

Seems to me like the name findM could be misleading
mapM :: (Monad m) = (a - m b) - [a] - m [b]
filterM :: (Monad m) = (a - m Bool) - [a] - m [a]

These take a monadic function and a list of elements. Yours works the other 
way around (takes a function and a list of 'monadic elements').
I'd expect the definition of findM to be:

findM'  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM' f [] = return Nothing
findM' f (x:xs) = do { b - f x; if b then return (Just x) else findM' f xs }

This one doesn't serve your purpose though.
J.A.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Why no findM ? simple Cat revisited

2002-11-20 Thread Ahn Ki-yung
Jorge Adriano wrote:

Seems to me like the name findM could be misleading
mapM :: (Monad m) = (a - m b) - [a] - m [b]
filterM :: (Monad m) = (a - m Bool) - [a] - m [a]

These take a monadic function and a list of elements. Yours works the other 
way around (takes a function and a list of 'monadic elements').
I'd expect the definition of findM to be:

findM'  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM' f [] = return Nothing
findM' f (x:xs) = do { b - f x; if b then return (Just x) else findM' f xs }

This one doesn't serve your purpose though.
J.A.
  


I appreciate your comment.
I agree that the type of findM should be the one you suggested,
and it still fits my original purpose. It's no more than a step arout.

\begin{code}

import IO
findM f [] = return Nothing
findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs }

isLeft (Left _) = True
isLeft _ = False

main = findM (=return.isLeft) (hCat stdin)
where hCat h = try (hGetLine h=putStrLn) : hCat h

\end{code}

I expetct the next Haskell Library Report includes findM.
It's obviously useful.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



simple cat by joining two infinite lists (intput/ouput)

2002-11-20 Thread Ahn Ki-yung
\begin{code}

import IO

findM f [] = return Nothing
findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs }

isLeft (Left _) = True
isLeft _ = False

main =
findM (=return.isLeft) $
map (try . uncurry (=)) $
zip (hGetCharS stdin) (hPutCharS stdout)
where
hGetCharS h = hGetChar h : hGetCharS h
hPutCharS h = hPutChar h : hPutCharS h

\end{code}

Joining input list and output list by uncurried =
IO errors such as EOF are enclosed by try.
findM finds those EOF or IO errors.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



library of monadic functions [was: Why no findM ? simple Cat revisited]

2002-11-20 Thread Jorge Adriano

 I appreciate your comment.
 I agree that the type of findM should be the one you suggested,
 and it still fits my original purpose. It's no more than a step arout.

 \begin{code}

 import IO
 findM f [] = return Nothing
 findM f (x:xs) = do { b - f x; if b then return (Just x) else findM f xs }

 isLeft (Left _) = True
 isLeft _ = False

 main = findM (=return.isLeft) (hCat stdin)
 where hCat h = try (hGetLine h=putStrLn) : hCat h

 \end{code}

Yes, you are right. 
It was enough because, you don't really care about what you found, you just 
want to search and stop when you do find something. You are returning the 
action that returned an element that satisfied your 
condition, not the actual element like before.

 I expetct the next Haskell Library Report includes findM.
 It's obviously useful.

I think both versions can be very useful:
findM  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
findM'  :: (Monad m) = (a - Bool) - [m a] - m (Maybe a)

Same can be said for,
takeWhileM :: (Monad m) = (a - m Bool) - [a] - m [a]
takeWhileM' :: (Monad m) = (a - Bool) - [m a] - m [a]

both would be usefull for different purposes.
Oh and since we're on it I also miss,
iterateM  :: (Monad m) = (a - m a) - a - m [a]
untilM :: (Monad m) = (a - m a) - a - m [a]
etc etc...

I've just been coding them as I need them, like many of you I suppose.
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: library of monadic functions [was: Why no findM ? simple Cat revisited]

2002-11-20 Thread Andrew J Bromage
G'day all.

On Wed, Nov 20, 2002 at 08:25:46PM +, Jorge Adriano wrote:

 I think both versions can be very useful:
 findM  :: (Monad m) = (a - m Bool) - [a] - m (Maybe a)
 findM'  :: (Monad m) = (a - Bool) - [m a] - m (Maybe a)

I can also make a case for:

  findM'' :: (Monad m) = (a - Bool) - [m a] - m a
  findM'' p [] = fail findM'': not found
  findM'' p (x:xs) = p x = \b - if b then return x else findM'' p xs

This goes with the philosophy that library functions shouldn't just
return Maybe.

Somewhere, somehow, there is a most general version of findM to be
found. :-)

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Random Color

2002-11-20 Thread Mike T. Machenry
I am trying to construct an infinate list of pairs of random colors.
I am hung up on getting a random color. I have:

data Color = Blue | Red | Green deriving (Eq, Ord, Show)

am I supposed to instantiate a Random class instance from color?
I am not sure exactly how the random number generator works. Is this
the best way to go about it? Should I instead get a random Integer
index of an array of Colors?

thanks,
-mike
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Random Color

2002-11-20 Thread Andrew J Bromage
G'day all.

On Wed, Nov 20, 2002 at 08:44:36PM -0500, Mike T. Machenry wrote:

 I am trying to construct an infinate list of pairs of random colors.
 I am hung up on getting a random color. I have:
 
 data Color = Blue | Red | Green deriving (Eq, Ord, Show)
 
 am I supposed to instantiate a Random class instance from color?

You could derive instances of Enum (and possibly also Bounded) and
create random elements that way.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Random Color

2002-11-20 Thread Mike T. Machenry
Andrew and list,

  I am a beginer. I really don't know what I would do if I derived
Color from Enum. You say I could create elements that way. Is there
some simple example someone could post to the list? Thank you for
your help.

-mike

On Thu, Nov 21, 2002 at 01:55:55PM +1100, Andrew J Bromage wrote:
 G'day all.
 
 On Wed, Nov 20, 2002 at 08:44:36PM -0500, Mike T. Machenry wrote:
 
  I am trying to construct an infinate list of pairs of random colors.
  I am hung up on getting a random color. I have:
  
  data Color = Blue | Red | Green deriving (Eq, Ord, Show)
  
  am I supposed to instantiate a Random class instance from color?
 
 You could derive instances of Enum (and possibly also Bounded) and
 create random elements that way.
 
 Cheers,
 Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe