[Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-04 Thread Dominic Steinitz
Here are some even older discussions on the subject. I don't know if anyone 
ever put them into a library or on the wiki.

Dominic.

http://haskell.org/pipermail/haskell-cafe/2005-May/009784.html

http://www.haskell.org//pipermail/libraries/2005-February/003143.html

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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-04 Thread Bulat Ziganshin
Hello Maurício,

Friday, February 03, 2006, 7:28:16 PM, you wrote:

M>I wonder if I could write a generic while based on your example:

while :: (a ->> IO a) -> (a -> Bool) -> IO ()

M>I'll probably learn something trying that.

i have about 5-10 imperative control structures defined in my
common lib, including while, until, forever, doInChunks


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-03 Thread Robert Dockins


On Feb 3, 2006, at 11:28 AM, Maurício wrote:

Kurt Hutchinson wrote:

On 2/2/06, Maurício <[EMAIL PROTECTED]> wrote:
  I understand those examples, but I really would like to know  
how to
do that with monads. I would like to ask the same question, but  
now with

this code:

double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};

An idiomatic approach:
example :: Double -> Double -> IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' <- readLn
example a' b'
main = example 1000 0


  Thanks! Robert's, Chris' and yours examples solved many of my  
questions. I understand I can insert modifications in IORefs (as  
used by Robert and Chris) inside the loop above:


| otherwise = do
 let a' = a / 2
 ...
 modifyIORef some_ioref some_function
 ...
 example a' b'

  I wonder if I could write a generic while based on your example:

while :: (a -> IO a) -> (a -> Bool) -> IO ()

  I'll probably learn something trying that.


FYI, here's a thread from a few months back about monad control  
structures; it may also provide some enlightenment.



http://www.haskell.org/pipermail/haskell-cafe/2005-October/011890.html



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-03 Thread Maurício

Kurt Hutchinson wrote:

On 2/2/06, Maurício <[EMAIL PROTECTED]> wrote:


  I understand those examples, but I really would like to know how to
do that with monads. I would like to ask the same question, but now with
this code:

double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};



An idiomatic approach:
example :: Double -> Double -> IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' <- readLn
example a' b'

main = example 1000 0


  Thanks! Robert's, Chris' and yours examples solved many of my 
questions. I understand I can insert modifications in IORefs (as used by 
Robert and Chris) inside the loop above:


| otherwise = do
 let a' = a / 2
 ...
 modifyIORef some_ioref some_function
 ...
 example a' b'

  I wonder if I could write a generic while based on your example:

while :: (a -> IO a) -> (a -> Bool) -> IO ()

  I'll probably learn something trying that.

  Best,
  Maurício

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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-02 Thread Kurt Hutchinson
On 2/2/06, Maurício <[EMAIL PROTECTED]> wrote:
>I understand those examples, but I really would like to know how to
> do that with monads. I would like to ask the same question, but now with
> this code:
>
> double a = 1000;
> double b = 0;
> while (a != b) {
>  a /= 2;
>  cout << a; // Prints a
>  cin << b; // User gives a number, stored in b
> };

An idiomatic approach:
example :: Double -> Double -> IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' <- readLn
example a' b'

main = example 1000 0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-02 Thread Chris Kuklewicz
Maurício wrote:

>   I understand those examples, but I really would like to know how to do
> that with monads. I would like to ask the same question, but now with
> this code:
> 
> double a = 1000;
> double b = 0;
> while (a != b) {
> a /= 2;
> cout << a; // Prints a
> cin << b; // User gives a number, stored in b
> };
> 

A close to line-for-line translation:

import Data.IORef
import Control.Monad(liftM2,when)

main = example 1000

example :: Double -> IO ()
example originalA = do
  refA <- newIORef originalA  -- allocate local variable a
  refB <- newIORef 0  -- allocate local variable b
  let loop = do   -- loop in scope of refA, refB
flag <- liftM2 (/=) (readIORef refA) (readIORef refB)
when flag $ do
  modifyIORef refA (/2)
  print =<< readIORef refA
  -- This will give an error if not a number:
  writeIORef refB =<< readIO =<< getLine
  loop
  loop -- start executing loop

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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-02 Thread Robert Dockins
I think you're looking for IORef http://www.haskell.org/ghc/docs/ 
latest/html/libraries/base/Data-IORef.html


Something like this (untested) should do what you want:

example :: IO ()
example = do { ref <- newIORef 1000; loop ref }
 where loop ref = do
   x <- readIORef ref
   print x
   when (x>1) (writeIORef ref (x/2) >> loop ref)


On Feb 2, 2006, at 10:57 AM, Maurício wrote:


Donald Bruce Stewart wrote:

briqueabraque:

 Hi,

 I would like to know what options I have in Haskell to do  
something similar to this C++ code:


double a = 1000;
while (a>1) a/=2;

 I'm able to do that with lists, but I would like to know how to  
do that with monads and variables with state.

You'll get good code using a normal recusive loop:
main = print (loop 1000)
where
loop a | a <= 1= a| otherwise  
= loop (a/2)

All such control structures may be implemented using recursion.
-- Don


  I understand those examples, but I really would like to know how  
to do that with monads. I would like to ask the same question, but  
now with this code:


double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};

  Best,
  Maurício


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




Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-02 Thread Maurício

Donald Bruce Stewart wrote:

briqueabraque:


 Hi,

 I would like to know what options I have in Haskell to do something 
similar to this C++ code:


double a = 1000;
while (a>1) a/=2;

 I'm able to do that with lists, but I would like to know how to do 
that with monads and variables with state.



You'll get good code using a normal recusive loop:

main = print (loop 1000)
where
loop a | a <= 1= a 
   | otherwise = loop (a/2)


All such control structures may be implemented using recursion.

-- Don


  I understand those examples, but I really would like to know how to 
do that with monads. I would like to ask the same question, but now with 
this code:


double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};

  Best,
  Maurício


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