Re: Prevent optimization from tempering with unsafePerformIO

2007-10-16 Thread Bernd Brassel
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
import Data.IORef
import System.IO.Unsafe

---
-- a generated data definition
---

data Bool' = True' | False' | Or Int [Bool']

---
-- two generated functions
---

ifThenElse :: Bool' - Bool' - Bool' - Bool'
ifThenElse True'  x y = x
ifThenElse False' x y = y
ifThenElse (Or i bs)  x y = Or i (map (\b - ifThenElse b x y) bs)

(|||) :: Bool' - Bool' - Bool'
x ||| y = ifThenElse x x y

--
-- the main goal to solve
--

main = do
  putStr 3 possibilities: 
  print (depthFirstSearch ((True' ? False') ||| (True' ? False')))
  putStr 2 possibilities: 
  print (depthFirstSearch (let x = True' ? False' in x ||| x))

-
-- a synopsis of the Curry core
-

depthFirstSearch :: Bool' - [Bool]
depthFirstSearch = dfs []

dfs :: [(Int,Int)] - Bool' - [Bool]
dfs _  True'   = [True]
dfs _  False'  = [False]
dfs st (Or i bs) = maybe (concat (zipWith (choose st i) bs [0..]))
 (dfs st . (bs!!))
 (lookup i st)

choose :: [(Int,Int)] - Int - Bool' - Int - [Bool]
choose st i b j = dfs ((i,j):st) b


---
-- unsafe part
---

(?) :: Bool' - Bool' - Bool'
x ? y = Or (unsafeNextOrRef ()) [x,y]

globalCounter :: IORef Int
globalCounter = unsafePerformIO (newIORef 0)

unsafeNextOrRef :: () - Int
unsafeNextOrRef _ = unsafePerformIO $ do
  r - readIORef globalCounter
  writeIORef globalCounter (r+1)
  return r
___
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 Bernd Brassel
Neil Mitchell schrieb:

 It varies by each piece of code, can you post a code fragment that
 gets optimised in the wrong way?

Sorry for posting this twice! I have added the code to the other thread.

Thanks!

Bernd
___
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: Prevent optimization from tempering with unsafePerformIO

2007-10-16 Thread Stefan O'Rear
On Tue, Oct 16, 2007 at 04:06:26PM +0200, 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.

Might I suggest, that the problem is your use of unsafePerformIO?  If
you use unsafePerformIO in accordance with the rules listed in the
specification (which happens to be the FFI addendum), -O options will
have no effect.  (Not that what you are trying to do is achievable with
correct use of unsafePerformIO; why do you want to do this unsafely,
instead of just using 'length'?  unsafePerformIO is a very slow
function, remember)

Stefan


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