[Haskell-cafe] Re: philosophy of Haskell

Paolo G. Giarrusso p.giarrusso at gmail.com
Fri Aug 27 06:08:41 EDT 2010


Hi all,
how comes that it is considered safe to use
Control.Monad.Primitive.primitive and .internal
[1]?
Why aren't they called, i.e.., unsafePrimitive and unsafeInternal?

primitive allows accessing the RealWorld state and, say, passing it
to two different IO actions unwrapped through internal? You get
unsafeInterleaveIO through 'safe' primitives.

Also, one could probably produce Haskell code showing all the
inconsistencies we discussed through these primitives, couldn't one?

[1] http://hackage.haskell.org/packages/archive/primitive/0.3/doc/html/Control-Monad-Primitive.html#v%3Aprimitive

After reading the subsequent discussion, I wanted to point out a
couple of further things - see below.

1) There is reason to this confusion: not only that state-passing
is used as the actual (inaccessible) implementation of IO, but also
that (it seems) the mistake used to be made by Haskell inventors - in
"Lazy Functional State Threads", at least (which is still cited as
documentation for Control.Monad.ST). "Tackling the Awkward Squad"
instead introduces this idea to later explain it does not work.

2) I cannot reconcile the result of the discussion with
referential transparency.
Is everybody wrong in claiming that Haskell is completely
referentially transparent?
"Lazy Functional State Threads" explicitly explains referential
transparency in terms of state passing.
I am now reading "Tackling the Awkward Squad", and from section 2.8 it
is already clear enough that IO is not referentially transparent
(although they never mention referential transparency in that paper).
In their example, after "let (c, world1) = getChar world0", replacing
c by "fst getChar world0" is not valid, and this violates referential
transparency.

See below for a more interesting example with concurrency.

On Aug 15, 5:30 pm, Ertugrul Soeylemez <e... at ertes.de> wrote:
> "Patai Gergely" <patai_gerg... at fastmail.fm> wrote:
> > > I don't agree.  A concurrent change is the effect of an IO action,
> > > not of the thread.  For example if a concurrent thread writes to an
> > > MVar, then that change becomes the effect of the next takeMVar,
> > > which gets executed.  If a concurrent thread changes a file on disk,
> > > then that changing becomes the effect of the next readFile, which
> > > reads the changed file.

> No.  As you say the world1 value is immutable, but that's not
> contradictory.  If between 'getLine' and 'print' something was done by a
> concurrent thread, then that change to the world is captured by 'print'.

Introducing a data race in your example creates another kind of
problem.
In your example, takeMVar is a synchronization primitive, and that
ensures that print always gives the same result:

>   var <- newEmptyMVar
>   forkIO $ threadDelay 1000000 >> putMVar var 15
>   takeMVar var >>= print

Let us make the example more interesting by introducing a data race on
a IORef:

ghci> var <- newIORef 10
ghci> (forkIO $ writeIORef var 20) >> readIORef var >>= print
10
ghci> readIORef var >>= print
20

Because of the data race, applying your reasoning, we get that either
readIORef or print has changed the value referred to by var. Which is
even more counterintuitive at best. I can remove the print from the
middle by saving the result of readIORef, apply the concept that
readIORef does not change the state to the first read, and obtain that
the second readIORef gives a different result on the same input and is
thus an impure function.

> nightmare = unsafePerformIO (getWrongWife >>= sex)
LOL

Greetings,
Paolo
--
Paolo Giarrusso - Ph.D. Student
http://www.informatik.uni-marburg.de/~pgiarrusso/


More information about the Haskell-Cafe mailing list