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

Reply via email to