Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-22 Thread Gregory Crosswhite
Thank you for the additional explanation, but it isn't clear that what  
you have added is inconsistent with my explanation.


The point I was trying to make is that in an impure/imperative world,  
you may assume that a function is called every time that you use it.   
However, in a pure world the assumption is that a function called with  
the same arguments will always return the same result (i.e.,  
referential transparency) so that you only need to run it's code once  
and then you can re-use that value henceforth.


In practice, of course, what happens under the hood (at least, with  
GHC) is that "foo <- mkNext" constructs a thunk named "foo" which is  
evaluated the at the first "print foo" and from then on the thunk is  
in an evaluated state and so later references to it just use this  
value rather than re-evaluating it.  This is because, due to  
referential transparency, it is equivalent to think of foo both as a  
function whose value can be cached and as a constant value that we  
just don't know yet.


The problem with the "foo" that was defined is that its code will  
actually give you a different value each time that you run it,  
violating the semantics of the language since all functions are  
assumed to be pure.  The problem with violating this semantic is that  
the compiler uses it whenever it can to make things more efficient,  
which in this case means treating foo as a value that only needs to be  
evaluated once even though each time you run the code you actually get  
a different result.  Hence, the results are in a sense undefined since  
the compiler is allowed to run foo as many times as it wants expecting  
to get the same result each time;  for example if two threads  
evaluated foo at the same time then under pathological conditions the  
first thread might see "1" and the second thread "2".


So the moral of this story --- and perhaps the point that you were  
trying to make --- is that it is better to think of "foo" as a  
constant value that you just don't know yet (until you evaluate) it  
rather than as a function that you can call.


(Your nitpick that "next" would have been a better name than "foo" is  
well taken, though.)


Cheers,
Greg

On Oct 22, 2009, at 12:48 AM, minh thu wrote:


2009/10/21 Gregory Crosswhite :
And just because this has not been explicitly stated:  it's not  
just for

aesthetic reasons that you couldn't do this with a pure function, but
because it violates the semantics and gets you the wrong result.   
So for

example, if you modified Tim's code to be

import Data.IORef
import System.IO.Unsafe
mkNext :: (Num a) => IO a
mkNext = do
 ref <- newIORef 0
 return . unsafePerformIO $
do
  modifyIORef ref (+1)
  readIORef ref
main :: IO ()
main = do
 foo <- mkNext
 print foo
 print foo
 print foo

Then the output that you will see (with GHC at least) is
1
1
1
because the compiler assumes that it only needs to evaluate foo  
once, after
which it can cache the result due to assumed referential  
transparency.

- Greg


This is indeed wrong, but not how you think it is.

The code you pass to unsafePerformIO has type Num a => IO a, so the
value passed to return has type Num a. So foo has type Num a too and
its value is 1.

Exactly like in

mkNext = do
 ref <- newIORef 0
 modifyIORef ref (+1)
 readIORef ref

which is a complicated way to write

mkNext = return 1

Now, it's clear that foo has value 1 and printing it three times
should output three 1. The whole point of having mkNext return an
action (that should be called next, and not foo, as it is much
clearer) in previous code was too be able to execute it multiple times
and having it return a new value.

In general, expecting

print bar
print bar
print bar

outputing three different things is wrong, as bar should be pure. If
bar is not pure, then it should be
a <- bar
print a
b <- bar
print b
c <- bar
print c

Cheers,
Thu


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


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-22 Thread minh thu
2009/10/21 Gregory Crosswhite :
> And just because this has not been explicitly stated:  it's not just for
> aesthetic reasons that you couldn't do this with a pure function, but
> because it violates the semantics and gets you the wrong result.  So for
> example, if you modified Tim's code to be
>
> import Data.IORef
> import System.IO.Unsafe
> mkNext :: (Num a) => IO a
> mkNext = do
>   ref <- newIORef 0
>   return . unsafePerformIO $
>  do
>modifyIORef ref (+1)
>readIORef ref
> main :: IO ()
> main = do
>   foo <- mkNext
>   print foo
>   print foo
>   print foo
>
> Then the output that you will see (with GHC at least) is
> 1
> 1
> 1
> because the compiler assumes that it only needs to evaluate foo once, after
> which it can cache the result due to assumed referential transparency.
> - Greg

This is indeed wrong, but not how you think it is.

The code you pass to unsafePerformIO has type Num a => IO a, so the
value passed to return has type Num a. So foo has type Num a too and
its value is 1.

Exactly like in

mkNext = do
  ref <- newIORef 0
  modifyIORef ref (+1)
  readIORef ref

which is a complicated way to write

mkNext = return 1

Now, it's clear that foo has value 1 and printing it three times
should output three 1. The whole point of having mkNext return an
action (that should be called next, and not foo, as it is much
clearer) in previous code was too be able to execute it multiple times
and having it return a new value.

In general, expecting

print bar
print bar
print bar

outputing three different things is wrong, as bar should be pure. If
bar is not pure, then it should be
a <- bar
print a
b <- bar
print b
c <- bar
print c

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


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread minh thu
2009/10/21 Tim Wawrzynczak :
> True...here we go then:
>
> import Data.IORef
> import System.IO.Unsafe
>
> mkNext :: (Num a) => IO (IO a)
> mkNext = do
>   ref <- newIORef 0
>   return (do modifyIORef ref (+1)
>  readIORef ref)
>
> next :: IO ()
> next = do
>   foo <- mkNext
>   a <- sequence [foo,foo,foo]
>   putStrLn $ show a
>
>
> running next will print [1,2,3] which is the result of calling 'foo' 3
> times.
>
> But technically then, mkNext is just an IO action which returns an IO action
> ;)
> and not a function which will return the next value each time it is called,
> hence the need to extract the value from mkNext, then use it...

That why it is called mkNext:

do next <- mkNext
 sequence [next, next, next]

>
> Cheers,
> Tim
>
>
> On Wed, Oct 21, 2009 at 1:30 PM, minh thu  wrote:
>>
>> 2009/10/21 Tim Wawrzynczak 
>> >
>> > Here's an example in the IO monad:
>> >
>> > import Data.IORef
>> > import System.IO.Unsafe
>> >
>> > counter = unsafePerformIO $ newIORef 0
>> >
>> > next = do
>> >   modifyIORef counter (+1)
>> >   readIORef counter
>> >
>> > Naturally, this uses unsafePerformIO, which as you know, is not
>> > kosher...
>>
>> But you don't close around the Ref like in your schemy example.
>>
>> mkNext = do
>>  ref <- newIORef 0
>>  return (do modifyIORef ref succ
>> readIORef ref)
>>
>> mimic your other code better.
>>
>> Cheers,
>> Thu
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread Gregory Crosswhite
And just because this has not been explicitly stated:  it's not just  
for aesthetic reasons that you couldn't do this with a pure function,  
but because it violates the semantics and gets you the wrong result.   
So for example, if you modified Tim's code to be



import Data.IORef
import System.IO.Unsafe

mkNext :: (Num a) => IO a
mkNext = do
  ref <- newIORef 0
  return . unsafePerformIO $
 do
   modifyIORef ref (+1)
   readIORef ref

main :: IO ()
main = do
  foo <- mkNext
  print foo
  print foo
  print foo


Then the output that you will see (with GHC at least) is

1
1
1

because the compiler assumes that it only needs to evaluate foo once,  
after which it can cache the result due to assumed referential  
transparency.


- Greg



On Oct 21, 2009, at 11:40 AM, Tim Wawrzynczak wrote:


True...here we go then:

import Data.IORef
import System.IO.Unsafe

mkNext :: (Num a) => IO (IO a)
mkNext = do
  ref <- newIORef 0
  return (do modifyIORef ref (+1)
 readIORef ref)

next :: IO ()
next = do
  foo <- mkNext
  a <- sequence [foo,foo,foo]
  putStrLn $ show a


running next will print [1,2,3] which is the result of calling 'foo'  
3 times.


But technically then, mkNext is just an IO action which returns an  
IO action ;)
and not a function which will return the next value each time it is  
called,

hence the need to extract the value from mkNext, then use it...

Cheers,
Tim


On Wed, Oct 21, 2009 at 1:30 PM, minh thu  wrote:
2009/10/21 Tim Wawrzynczak 
>
> Here's an example in the IO monad:
>
> import Data.IORef
> import System.IO.Unsafe
>
> counter = unsafePerformIO $ newIORef 0
>
> next = do
>   modifyIORef counter (+1)
>   readIORef counter
>
> Naturally, this uses unsafePerformIO, which as you know, is not  
kosher...


But you don't close around the Ref like in your schemy example.

mkNext = do
 ref <- newIORef 0
 return (do modifyIORef ref succ
readIORef ref)

mimic your other code better.

Cheers,
Thu

___
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] Simple but interesting (for me) problem

2009-10-21 Thread Tim Wawrzynczak
True...here we go then:

import Data.IORef
import System.IO.Unsafe

mkNext :: (Num a) => IO (IO a)
mkNext = do
  ref <- newIORef 0
  return (do modifyIORef ref (+1)
 readIORef ref)

next :: IO ()
next = do
  foo <- mkNext
  a <- sequence [foo,foo,foo]
  putStrLn $ show a


running next will print [1,2,3] which is the result of calling 'foo' 3
times.

But technically then, mkNext is just an IO action which returns an IO action
;)
and not a function which will return the next value each time it is called,
hence the need to extract the value from mkNext, then use it...

Cheers,
Tim


On Wed, Oct 21, 2009 at 1:30 PM, minh thu  wrote:

> 2009/10/21 Tim Wawrzynczak 
> >
> > Here's an example in the IO monad:
> >
> > import Data.IORef
> > import System.IO.Unsafe
> >
> > counter = unsafePerformIO $ newIORef 0
> >
> > next = do
> >   modifyIORef counter (+1)
> >   readIORef counter
> >
> > Naturally, this uses unsafePerformIO, which as you know, is not kosher...
>
> But you don't close around the Ref like in your schemy example.
>
> mkNext = do
>  ref <- newIORef 0
>  return (do modifyIORef ref succ
> readIORef ref)
>
> mimic your other code better.
>
> Cheers,
> Thu
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread Alex Queiroz
Hallo,

On 10/21/09, Tim Wawrzynczak  wrote:
> Here's an example in the IO monad:
>
> import Data.IORef
> import System.IO.Unsafe
>
> counter = unsafePerformIO $ newIORef 0
>
> next = do
>   modifyIORef counter (+1)
>   readIORef counter
>
> Naturally, this uses unsafePerformIO, which as you know, is not kosher...
>

 This is different because counter is global.

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


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread minh thu
2009/10/21 Tim Wawrzynczak 
>
> Here's an example in the IO monad:
>
> import Data.IORef
> import System.IO.Unsafe
>
> counter = unsafePerformIO $ newIORef 0
>
> next = do
>   modifyIORef counter (+1)
>   readIORef counter
>
> Naturally, this uses unsafePerformIO, which as you know, is not kosher...

But you don't close around the Ref like in your schemy example.

mkNext = do
  ref <- newIORef 0
  return (do modifyIORef ref succ
 readIORef ref)

mimic your other code better.

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


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread Tim Wawrzynczak
Here's an example in the IO monad:

import Data.IORef
import System.IO.Unsafe

counter = unsafePerformIO $ newIORef 0

next = do
  modifyIORef counter (+1)
  readIORef counter

Naturally, this uses unsafePerformIO, which as you know, is not kosher...

Cheers,
 - Tim

On Wed, Oct 21, 2009 at 1:00 PM, Tim Wawrzynczak wrote:

> I'm guessing the function looks something like this? (this is common lisp
> not scheme)
>
> (let ((counter 0))
>   (defun next ()
> (incf counter)
> counter))
>
> So the first time you call (next), it returns 1, then 2, etc.
> The function (next) is a closure over the variable 'counter' and acts by
> incrementing the variable counter, which is only visible in the scope of the
> let-block.  As you know in Haskell there is no mutable state (outside of
> certain monads), so a function like must take place in a monad which allows
> this, such as IO or ST.  You would probably have to allocate an IORef or
> STRef which is local to the next function (effectively creating a closure
> over it).
>
> Cheers,
>  - Tim
>
>
> On Wed, Oct 21, 2009 at 12:34 PM, michael rice  wrote:
>
>>  There's a thread on the plt-scheme list about creating a function of NO
>> arguments named NEXT that just returns the number of times it's been called,
>> a piece of cake in Scheme, but how would one do this in Haskell? Would the
>> best approach be to use a State monad?
>>
>> Michael
>>
>> ___
>> 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] Simple but interesting (for me) problem

2009-10-21 Thread Tim Wawrzynczak
I'm guessing the function looks something like this? (this is common lisp
not scheme)

(let ((counter 0))
  (defun next ()
(incf counter)
counter))

So the first time you call (next), it returns 1, then 2, etc.
The function (next) is a closure over the variable 'counter' and acts by
incrementing the variable counter, which is only visible in the scope of the
let-block.  As you know in Haskell there is no mutable state (outside of
certain monads), so a function like must take place in a monad which allows
this, such as IO or ST.  You would probably have to allocate an IORef or
STRef which is local to the next function (effectively creating a closure
over it).

Cheers,
 - Tim


On Wed, Oct 21, 2009 at 12:34 PM, michael rice  wrote:

> There's a thread on the plt-scheme list about creating a function of NO
> arguments named NEXT that just returns the number of times it's been called,
> a piece of cake in Scheme, but how would one do this in Haskell? Would the
> best approach be to use a State monad?
>
> Michael
>
> ___
> 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] Simple but interesting (for me) problem

2009-10-21 Thread minh thu
2009/10/21 michael rice 
>
> There's a thread on the plt-scheme list about creating a function of NO 
> arguments named NEXT that just returns the number of times it's been called, 
> a piece of cake in Scheme, but how would one do this in Haskell? Would the 
> best approach be to use a State monad?

If you really want no argument, not just syntactically in the do
notation, you need ST or IO. Furthermore, you need ST or IO to
allocate a mutable variable that is accessible only to the next
function.

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


Re: [Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread Brent Yorgey
On Wed, Oct 21, 2009 at 10:34:47AM -0700, michael rice wrote:
> There's a thread on the plt-scheme list about creating a function of NO 
> arguments named NEXT that just returns the number of times it's been called, 
> a piece of cake in Scheme, but how would one do this in Haskell? Would the 
> best approach be to use a State monad?

Yes, a State monad would be the way to go.  Such a function cannot
have type () -> Int in Haskell, because a function with type () -> Int
must be pure: in particular it would always have to give the same
output.  So giving the function the type () -> State Int Int (or
really, just State Int Int) makes explicit the fact that evaluating it
has a state effect.

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


[Haskell-cafe] Simple but interesting (for me) problem

2009-10-21 Thread michael rice
There's a thread on the plt-scheme list about creating a function of NO 
arguments named NEXT that just returns the number of times it's been called, a 
piece of cake in Scheme, but how would one do this in Haskell? Would the best 
approach be to use a State monad?

Michael


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