Re: Prevent optimization from tempering with unsafePerformIO

2007-10-17 Thread David Sabel

Hi Bernd,

Bernd Brassel wrote:

Hi David,

thank you! This is really useful information!

  
I think it's the let floating (out) together with common subexpression 
elimination:


 > ghc --make -O2 -no-recomp -fno-cse  -o curry-no-cse  curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-cse ...
 > ghc --make -O2 -no-recomp -fno-full-laziness  -o curry-no-fll  curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-fll ...
 > ghc --make -O2 -no-recomp -fno-full-laziness -fno-cse  -o 
curry-no-cse-no-fll  curry.hs

[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-cse-no-fll ...
 > ./curry-no-cse
3 possibilities: [True,False]
2 possibilities: [True,False]
 > ./curry-no-fll
3 possibilities: [True,False]
2 possibilities: [True,False]
 > ./curry-no-cse-no-fll
3 possibilities: [True,True,False]
2 possibilities: [True,False]



I will try this on large scale Curry programs. I hope the remaining
optimizations will still do some good. Do you think that there is a way
to be more selective? I mean to select those parts of the program which
can and which cannot be optimized?
  
I think this would require an analysis of the code during compilation 
(to split into "pure" parts and "impure" parts),

but we did not investigate this.

  
ps.: Maybe it is interesting to look at HasFuse [1] (somewhat outdated), 
but it exactly forbids both transformations


[1] http://www.ki.informatik.uni-frankfurt.de/research/diamond/hasfuse/



Yes, that looks interesting, too. Are there plans to update it with the
ghc?
  
Honestly, we did nothing since 2004 on the code, but maybe we could port 
the changes to the current source of ghc.


I remember that in an early version of ghc (I think < 5) there was an option
-O file which gave the user control over the optimizations with a script,
this would probably a nice feature to have again...

Regards,
David

Thanks for your hints!
Bernd
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
  


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Prevent optimization from tempering with unsafePerformIO

2007-10-16 Thread David Sabel

Hi,

I think it's the let floating (out) together with common subexpression 
elimination:


> ghc --make -O2 -no-recomp -fno-cse  -o curry-no-cse  curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-cse ...
> ghc --make -O2 -no-recomp -fno-full-laziness  -o curry-no-fll  curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-fll ...
> ghc --make -O2 -no-recomp -fno-full-laziness -fno-cse  -o 
curry-no-cse-no-fll  curry.hs

[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-cse-no-fll ...
> ./curry-no-cse
3 possibilities: [True,False]
2 possibilities: [True,False]
> ./curry-no-fll
3 possibilities: [True,False]
2 possibilities: [True,False]
> ./curry-no-cse-no-fll
3 possibilities: [True,True,False]
2 possibilities: [True,False]

Regards,
David

ps.: Maybe it is interesting to look at HasFuse [1] (somewhat outdated), 
but it exactly forbids both transformations


[1] http://www.ki.informatik.uni-frankfurt.de/research/diamond/hasfuse/



Bernd Brassel wrote:

Hi Neil, hi Don!

Nice meeting you at ICFP by the way.

  

Can you give a specific example of what you have tried to do, and how it
failed?



I have attached a short synopsis of what our Curry to Haskell
conceptually does. I could explain what all the parts mean and why they
are defined this way, if it is important. On first glance it looks
as if we were doing unsafe things in the very worst way. But the
invariants within the generated code clean up things again. E.g., the
result of main does not at all depend on whether or not the program is
evaluated eagerly or lazily.

I hope it is okay that I did not add any no-inline pragmata or something
like that. Unfortunately, I forgot all the things we have tried more
than a year ago to make optimization work.

But this is the way it should work:

$ ghc --make -O0 -o curry-no-opt curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-no-opt ...
$ curry-no-opt
3 possibilities: [True,True,False]
2 possibilities: [True,False]

and this is what happens after optimization:

$ rm curry.hi curry.o
$ ghc --make -O2 -o curry-opt curry.hs
[1 of 1] Compiling Main ( curry.hs, curry.o )
Linking curry-opt ...
$ curry-opt
3 possibilities: [True,False]
2 possibilities: [True,False]

As the code is now that is no surprise. But how can I prevent this from
happening by adding pragmata?

Thanks a lot for your time!

Bernd
  



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unsafePerformIO and NOINLINE Pragma

2005-09-13 Thread David Sabel
Hi,

> Hi!
> 
> I want to analyse the laziness of a data structure. To check how many nodes 
> are constructed I use a global counter.
> 
> counter :: IORef Int
> counter = unsafePerformIO (newIORef 0)
> 
> This counter is increased every time the constructor is called by redefining 
> the constructor OBDD as follows.
> 
> oBDD low var high =
>   seq (unsafePerformIO (modifyIORef counter (+1))) (OBDD low var high)
> 
> This works fine. 
> When I compile with optimisations the counter is always set to one no matter 
> how many nodes are constructed. I thought this would be caused by inlining. 
> Therefore I have added two NOINLINE pragmata.
> 
> {-# NOINLINE counter #-}
> {-# NOINLINE oBDD #-}
> 
> Although the counter doesn't work. Is there another optimisation that can 
> cause harm? Is there something wrong with the pragmata?

Two comments:
1. There are other optimisations than inlining that can break sharing, e.g. 
   common subexpression elimination, full-laziness-transformation.

2. I tested the following:

  {-# NOLINE counter #-}
  {-# INLINE oBDD #-}

  then the counter "seems" to work correct.  In my opinion 
  oBDD is an abstraction and can always be inlined.

Cheer,
  David
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldr f (head xs) xs is not the same as foldr1 f xs

2005-05-08 Thread David Sabel
Ah! thanks you're right, sorry.
My  problem  arose from the fact that
let x = 'A':undefined in head $ (unwords.words) x
does not terminate, but now it's clear: For interspersing the blanks you 
need to evaluate the tail.

Sorry again.
Cheers,
 David
Tomasz Zielonka schrieb:
On Sun, May 08, 2005 at 08:14:30PM +0200, David Sabel wrote:
 

Hi!
Subject: foldr f (head xs) xs  is not the same as foldr1 f xs
   

I think you forgot about tail: 

foldr f (head xs) (tail xs)
Best regards
Tomasz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


foldr f (head xs) xs is not the same as foldr1 f xs

2005-05-08 Thread David Sabel
Hi!

A small example for the claim mentioned in the subject:

Prelude> let x = 1:undefined in foldr (curry fst) (head x) x
1
Prelude> let x = 1:undefined in foldr1 (curry fst)  x
*** Exception: Prelude.undefined

Perhaps it would be better to change the implementation of foldr1?

Cheers,
  David
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: turn off let floating

2004-04-29 Thread David Sabel
Hi,


> > Results:
> > 
> >method  runtime (s)
> >---
> >pure0.7
> >ffi 3.2
> >fastMut 15
> >ioref   23
> 
> I very strongly suspect that it is the unsafePerformIO that hurts
> performance in the fastMut case.  Otherwise this case would be around
> the same speed as the FFI example, perhaps faster.
> 
> You could try out that theory by copying the definition of
> unsafePerformIO into your code, and putting an INLINE pragma on it.  I
> think it's safe to do this in your case (it's not safe in general).

That's interesting for me, in which situations isn't it safe to inline
the definition of unsafePerformIO? 

David
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: turn off let floating

2004-04-09 Thread David Sabel
Hi,
 
you can turn off let-floating by compiling without optimizations,
i.e. without using a -O flag or using -O0 explicitly. 
The disadvantage is that most of all other optimizations 
are turned off too.
 
Another possibility would be to compile your program with HasFuse 
 
http://www.ki.informatik.uni-frankfurt.de/~sabel/hasfuse/
 
which is a modification of GHC, that performs only such transformations
that are compatible with the use of unsafePerformIO.
(no common subexpression elimination,
 no let-floating out,
 more restrictive inlining)
 
In fact, HasFuse guarantees more than compiling SAFE uses of 
unsafePerformIO correctly (it fulfills the FUNDIO-semantics),
but HasFuse can also be used to compile 'normal' Haskell programs.
 
David
--
JWGU Frankfurt, Germany


- Original Message - 
From: "Bernard James POPE" <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Cc: "Bernard James POPE" <[EMAIL PROTECTED]>
Sent: Tuesday, April 06, 2004 10:24 AM
Subject: turn off let floating


> Hi all,
> 
> In the documentation for System.IO.Unsafe
> it says:
> 
>Make sure that the either you switch off let-floating, 
>or that the call to unsafePerformIO cannot float outside a lambda.  
> 
> My question is how can you turn off let floating? I can't seem to
> find a flag that suggests this behaviour.
> 
> Cheers,
> Bernie.
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: strange behaviour

2003-08-14 Thread David Sabel
> On 2003-08-11 at 11:44+0200 "David Sabel" wrote:
> > module Main(main) where
> >
> > import System.IO.Unsafe
> >
> > main = case unsafePerformIO (print "test") of
> > () -> main
> >
> >
> > ok, probably I use unsafePerformIO in an "unsafe" way and so on,
> > but executing the program prints infinitely often "test" on the screen,
> > but I think it would be correct to do so one time?
>
> It's correct behaviour to print "test" any number of
> times. Haskell is non-strict, which only means that things
> aren't evaluated unless needed. It's not (defined to be)
> lazy, which would mean that named expressions would be
> evaluated at most once (though ghc meets this). It's also
> not defined to be "fully lazy" meaning that unnamed
> expressions would be evaluated at most once in any given
> closure. So GHC is entirely within its rights to evaluate
> <> any number of times, or
> possible even none, since it knows that that expression
> always returns the same value ().

Thanks for your comments.

Ok, Haskell is not lazy, an "referential transparency" allows you
to evalute (unsafePerformIO print "test") as often you want.

But GHC provides to to do sharing in
some sense and the compilation should be "Work-safe".

My point here is to know, what's the reason for the different
behaviour, rather than discussing the
correctness of using unsafePerformIO.


>
> So you /have/ used it in an unsafe way, and the above
> discussion illustrates why unsafePerformIO really is
> completely unsafe.
>
>   Jón
>
> --
> Jón Fairbairn [EMAIL PROTECTED]
>
>
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: strange behaviour

2003-08-14 Thread David Sabel
Ok, thanks for all your comments.

But I think that the examples haven't much to do
with the core-to-core optimisations, because I've also used
a modified version --modified be me ;-) --  of ghc5.04.3,
where only a modified simplifying is done. The modifications
are small: Do Inlining only for values, do only trivial eta-expansion
(not for case, let and so on) , and some other "small" things.

But with this modified compiler, the same problem comes up.

I didn't modify things after simplifying, espcially generating STG-Code
or transforming (optimising) this code.

I think it has something to do with the STG-Code generation or
with normal code generation, and it depends on the fact, if
the function is exported or not.
Any hints in this direction???

Thanks,
  David



- Original Message -
From: "Simon Marlow" <[EMAIL PROTECTED]>
To: "David Sabel" <[EMAIL PROTECTED]>; "Jon Fairbairn"
<[EMAIL PROTECTED]>
Cc: <[EMAIL PROTECTED]>
Sent: Monday, August 11, 2003 12:40 PM
Subject: RE: strange behaviour


>
> > My point here is to know, what's the reason for the different
> > behaviour, rather than discussing the
> > correctness of using unsafePerformIO.
>
> The reason is this:  GHC uses a lazy evaluation strategy, as opposed to
> fully-lazy.  Under lazy evaluation, the unsafePerformIO expression in
> your example will be evaluated each time main is invoked.
>
> When -O is turned on, GHC performs some transformations on the code that
> have the effect of changing the evaluation strategy to "almost
> fully-lazy".  That is, there will be some more sharing, but not
> necessarily as much as you would get in a compiler that implements
> fully-lazy evaluation.
>
> Indeed, even without -O, you might get a bit more sharing than you would
> under pure lazy evaluation.
>
> Of course, you should never write any code that depends on any of this.
>
> Cheers,
> Simon
>
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


strange behaviour

2003-08-11 Thread David Sabel
Hi,

the following "toy" program has a strange behaviour,
when compiling with ghc5.04.3 an no optimisation (-O0)

module Main(main) where

import System.IO.Unsafe

main = case unsafePerformIO (print "test") of
() -> main


ok, probably I use unsafePerformIO in an "unsafe" way and so on,
but executing the program prints infinitely often "test" on the screen,
but I think it would be correct to do so one time?

I think it has something to do with exporting main, because the
following program

module Main(main) where

import System.IO.Unsafe

main = seq f (return ())

f = case unsafePerformIO (print "test") of
 () -> f

behaves ok.

Does someone, what's the reason for this?

Thanks,
  David

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: case-identity

2003-07-28 Thread David Sabel
> In Core, the list of alternatives is always exhaustive.

Ok, thanks. 
So I assume the "dead alternative elimination" is no longer done in
the simplifier?

(
The dead alternative elimination is defined as:

 case x of===> case x of
   P1 -> E1  P1 -> E1
   ...   ...
   ci a1 ... an -> EiPn -> En
   ...   [without ci a1 ... an -> Ei]
   Pn -> En

if x is not of constructor c_i
)

David

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


case-identity

2003-07-23 Thread David Sabel
Hi,

the case-identity transformation is

case e of
 pat1 -> pat1 ===>   e
 ...
 patn -> patn

It's performed in SimplUtils.mkCase1.

My (very special) question is: How do you ensure, that
 there's a case-alternative for every constructor of the type of e?

Otherwise you could transform

case e of {True -> True} ===> True, if e is of type Bool, 

but that't not correct if e is False.

Maybe you add a default-alternative DEFAULT -> error ... ?

Thanks,

 David
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: case-eta-expansion

2003-07-21 Thread David Sabel

- Original Message -
From: "Simon Peyton-Jones" <[EMAIL PROTECTED]>
To: "David Sabel" <[EMAIL PROTECTED]>;
<[EMAIL PROTECTED]>
Sent: Monday, July 21, 2003 9:53 AM
Subject: RE: case-eta-expansion


> Not quite sure what you mean by "case eta expansion".

I mean this transformation:
case e of {p1 -> e1,...,pn -> en}
===> \y -> case e of {p1 -> e1 y, ..., pn -> en y}

which is described in Santos' PhD thesis as a special
form of eta-expansion which is done in 'special' situations.

> Eta expansion is certainly still done, but only on 'let'
> right-hand-sides, by SimplUtils.tryEtaExpansion.

Ok, thanks

David

>
> Simon
>
> | -Original Message-
> | From: [EMAIL PROTECTED]
> [mailto:[EMAIL PROTECTED]
> | On Behalf Of David Sabel
> | Sent: 18 July 2003 14:02
> | To: [EMAIL PROTECTED]
> | Subject: case-eta-expansion
> |
> | Hi,
> |
> | Can someone tell me, where exactly (in the code of ghc5.04.3)
> | the case-eta-expansion is performed, I searched
> | the modules of the simplifier, but didn't find this transformation.
> |
> | Or is it no longer performed in ghc5.04.3?
> |
> | Thanks,
> |
> |  David
> |
> |
> | ___
> | Glasgow-haskell-users mailing list
> | [EMAIL PROTECTED]
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


case-eta-expansion

2003-07-18 Thread David Sabel
Hi,

Can someone tell me, where exactly (in the code of ghc5.04.3)
the case-eta-expansion is performed, I searched
the modules of the simplifier, but didn't find this transformation.

Or is it no longer performed in ghc5.04.3?

Thanks,

 David


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Modifying the simplifier

2003-04-02 Thread David Sabel
Is there an easy way to turn off some of the local transformations in
the simplifier?

The background:
I'm writing my master thesis about compiling the unsafePerformIO in a "safe"
way
in the ghc. For that I used a nondeterministic semantics which simulates the
IO.
After a lot of theoretical work it has pointed out, that some of the local
transformations
of the ghc are no longer correct (from my point of view). Now I want to
implement a prototype by
modifying the ghc. Especially the eta-expansion, case-elimination must be
turned off,
inling in general is'nt correct too, so I would like to turn it off for now
and
later modify the implementation for this transformation.

David Sabel
---
JWGU Frankfurt


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Question about literals in the core-language

2003-01-13 Thread David Sabel
Hello,

I'm working at comparing the ghc-core-language with another lambda-calculus.
This calculus has no unboxed values, but normal constructors are available.
My problem is now: How can I represent the unboxed values in my calculus.
More precisely: Can I represent the unboxed values by a finite set of
constants,
or include the literals also integers, which can be infinite? If that is the
case,
how are the (unboxed) integers represented in the ghc-core-language?

Thanks for your comments!

David Sabel
-
JWGU Frankfurt

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Translating seq into Core

2003-01-03 Thread David Sabel
Thanks for that answer. I suggested something like that.
Can you explain me, how the Haskell-expression 
case a of b -> e (in Haskell, not strict, right?)
ist translated to Core?




> seq a b = case a of { DEFAULT -> b }
> 
> In Core, case is always strict.
> 
> | -Original Message-
> | From: David Sabel [mailto:[EMAIL PROTECTED]]
> | Sent: 03 January 2003 14:11
> | To: [EMAIL PROTECTED]
> | Subject: Translating seq into Core
> | 
> | Hallo,
> | 
> | my question ist, how the "seq" operator is translated into the
> | GHC-core-language?
> | 
> | I had suspected, the core-language has a special strictness-operator,
> but I
> | saw, that this is not the case.
> | 
> | 
> | David Sabel
> | JWGU Frankfurt
> | 
> | ___
> | Glasgow-haskell-users mailing list
> | [EMAIL PROTECTED]
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Translating seq into Core

2003-01-03 Thread David Sabel
Hallo,

my question ist, how the "seq" operator is translated into the
GHC-core-language?

I had suspected, the core-language has a special strictness-operator, but I
saw, that this is not the case.


David Sabel
JWGU Frankfurt

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Optimisation and unsafePerformIO

2002-10-30 Thread David Sabel

- Original Message - 
From: "Albert Lai" <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Sent: Wednesday, October 30, 2002 7:35 AM
Subject: Re: Optimisation and unsafePerformIO


> "David Sabel" <[EMAIL PROTECTED]> writes:
> 
> > {-# NOINLINE b #-}
> > 
> > b x  = if even x then unsafePerformIO getChar else bot
> > 
> > bot = bot
> > 
> > main = do
> >  putChar (b 4)
> >  putChar (b 6)
> 
> I am not a compiler implementer (or lawyer, for that matter :)
> But I propose this guess.  First, both even 4 and even 6 get
> constant-folded to True; so b 4 and b 6 both become unsafePerformIO
> getChar.  Then there is a common subexpression elimination.

No! I used the option -fno-cse, what means that common supexpression
elimination is turned off.

> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Optimisation and unsafePerformIO

2002-10-28 Thread David Sabel
Of course, I used unsafePerformIO in an unsafe way!
I'm thinking about a way to make unsafePerformIO safe.
Therefore the compiler can't do any transformation the ghc does and I want
to locate these transformations.


- Original Message -
From: "Simon Marlow" <[EMAIL PROTECTED]>
To: "David Sabel" <[EMAIL PROTECTED]>;
<[EMAIL PROTECTED]>
Sent: Monday, October 28, 2002 10:41 AM
Subject: RE: Optimisation and unsafePerformIO


> Consider the following program:
>
> -
> {-# NOINLINE b #-}
>
> b x  = if even x then unsafePerformIO getChar else bot
>
> bot = bot
>
> main = do
>  putChar (b 4)
>  putChar (b 6)
>
> -
>
> when you compile the programm with the options: -O0
> and execute the program you get:
> > test
> ab  (That's the input)
> ab  (That's the ouput)
>
> when you compile the programm with the options: -O1 -fno-cse
> you get:
> > test
> ab
> aa

You are using unsafePerformIO in an unsafe way.  The meaning of your
program depends on whether the compiler implements full laziness or not,
which is a decision left entirely up to the compiler implementor.  If
you want to write portable code, don't use unsafePerformIO in this way.

What exactly is it you're trying to achieve?  Perhaps we can suggest a
better solution.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Optimisation and unsafePerformIO

2002-10-27 Thread David Sabel
Consider the following program:

-
{-# NOINLINE b #-}

b x  = if even x then unsafePerformIO getChar else bot

bot = bot

main = do
 putChar (b 4)
 putChar (b 6)

-

when you compile the programm with the options: -O0
and execute the program you get:
> test
ab  (That's the input)
ab  (That's the ouput)

when you compile the programm with the options: -O1 -fno-cse
you get:
> test
ab
aa

my question is now: which transformation/optimisation is responsible for
that, and is it
possible to switch off this transformation?

David Sabel


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Problem with ghc-5-04-1.msi

2002-10-23 Thread David Sabel
The error occurs before I have this choice.


> Hi there,
> 
> the installer gives you a choice between "Typical", "Custom",
> and "Complete" -- choose the "Custom" option to pick an
> installation location other than the default.
> 
> hth
> --sigbjorn
> 
> - Original Message -
> From: David Sabel
> To: [EMAIL PROTECTED]
> Sent: Wednesday, October 23, 2002 05:43
> Subject: Problem with ghc-5-04-1.msi
> 
> 
> While installing the file the following error occurs:
> Invalid Drive c:\
> 
> after that error message the "GHC setup ended prematurely because of an
> error"
> 
> My Computer doesn't have a drive c:\, the windows partition is on d:\.
> 
> The previous .msi-Version (5.04) didn't have this error.
> 
> David
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Problem with ghc-5-04-1.msi

2002-10-23 Thread David Sabel



While installing the file the following error 
occurs:
Invalid Drive c:\
 
after that error message the "GHC setup ended 
prematurely because of an error"
 
My Computer doesn't have a drive c:\, the 
windows partition is on d:\.
 
The previous .msi-Version (5.04) didn't have this 
error.
 
David
 
 


Re: unsafePerformIO

2002-10-09 Thread David Sabel


- Original Message -
From: "Simon Marlow" <[EMAIL PROTECTED]>
Sent: Tuesday, September 24, 2002 2:58 PM
Subject: RE: unsafePerformIO

[...]


> As for sharing, we currently don't provide any guarnatees, although we
> should.  It is currently the case that if you write
>
> a = unsafePerformIO (putStr "hello")
> b = unsafePerformIO (putStr "hello")
>
> and both a and b are evaluated, then you may get either one or two
> "hello"s on stdout.  You can currently make things more deterministic by
> (a) adding NOINLINE pragmas for a and b, and (b) using the flag -fno-cse
> to disable common sub-expression elimination.  Then you'll get exactly
> two instances of "hello" on stdout, although we won't guarantee that
> behaviour for ever.  At some point we'll fix it so that unsafePerformIO
> applications are never duplicated or coalesced.


Are there any (short) examples available where using of unsafePerformIO
leads to unexpected behaviour,
especially an example with the terms a and b from above?

with best regards, David

-
JWGU Frankfurt

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Question about the notation of (# ... #)

2002-10-04 Thread David Sabel

Hi,

can somebody explain what the notation (# ... #)
means?

For example it is used in the definition of unsafePerformIO:

unsafePerformIO :: IO a -> a
unsafePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r

Thanks, David


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: IO-System

2002-10-01 Thread David Sabel



> > I'm, analysing the IO-system of the GHC and need more
> > information about
> > it.
> > More precisely: How switches the run-time-system between (normal)
> > evaluation and performing of IO-actions?
> >
> > I read the rts-paper, but didn't find any information about this.
> >
> > Can somebody give a short review, or are ther any other
> > papers available?
>
> The runtime system mostly has no concept of IO vs. non-IO evaluation.
> The IO monad is implemented as the following type:
>
>   newtype IO a = IO (State# RealWorld ->
>(# State# RealWorld, a #)
>
> which means that an IO action is simply a function from the world state
> to a pair of a new world state and a value.  In other words, it's a
> straightfoward state monad, except that we use some optimised
> representations to eliminate some of the overhead of passing the state
> around.
>
> Cheers,
> Simon

In the GHC users guide Chapter 7.2.12 is the single primitve value
realWorld# of the state of the world provided.
This value is also used in the implementation of unsafePerformIO
(GHC.IOBase), where it is applied as the argument
to the IO action, and so on (after performing the action it's discarded).

My question is now: Is the same value (realWorld#) applied while using
normal monadic - not unsafe - IO, more precisely
is a programm main::IO () executing the expression (main realWorld#)?

David



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



unsafePerformIO

2002-09-20 Thread David Sabel

In read your paper ""Tackling the Awkward Squad: monadic input / output,
concurrency, exceptions, and foreign-language calls in Haskell",  and have
a question about unsafePerformIO.

In your operational semantic of the IO-Monad you tell nothing about, how
'unsafe' IO actions are performed, is there another paper / documentation
about
this available, or can you - or someone else - give me a review about that?

David
JWGU Frankfurt


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: IO-System

2002-09-17 Thread David Sabel

[...]
> I think the query
> originally
> assumed a sequencing ambiguity in the IO monad... but in my experiance
> (all be it  limited) the IO monad is there to ensure strict sequencing.

You're right, this was my main question. I read the paper "Tackling the
Awkwar Squad: monadic input / output, concurrency, exceptions, and
foreign-language calls in Haskell", Simon Peyton Jones, available at
http://research.microsoft.com/users/simonpj

There is an operational semantic given for the IO system,
and  I think this semantic ensures strict sequencing of IO actions.

In this paper the echoTwice-example is given, and I was a little bit
confused about the abnormal behavior of the program when I executed it.
I didn't think at the buffering, but now it seem to be clear...

Thanks for your comments

---
David Sabel
JWGU Frankfurt

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users