Re: Rule question.

1999-07-08 Thread Kevin Atkinson

Simon Peyton-Jones wrote:

 Sorry it's taken me a long time to look at this.
 Two things are going on here.

No problem

   module KevinB where
 
   data Arr ix el = Arr Int [(ix,el)] deriving Show
 
   replaceMany :: [(ix,el)] - Arr ix el - Arr ix el
   replaceMany = error "In Replace Many"
 
   {-# RULES
  "rule1" forall f,l,a. replaceMany (map f l) a = replaceManyMap f l a
#-}
 
   replaceManyMap :: (v - (ix,el)) - [(ix,el)] - Arr ix el - Arr ix el
   replaceManyMap = error "In Replace Many Map"
 
   arr s l = let a = Arr s [] in
 replaceMany l a
 
 If you compile this, replaceMany will be inlined in arr's defn,
 which means that anyone importing KevinB won't see the version
 of arr that has replaceMany in it.  So
 
 module KevinA where
 import KevinB
 arr2 s l = arr s (map (\(i,e)-(i+2,e)) l)
 
 will not fire the rule.
 
 Solution: add an INLINE pragma to 'arr'.   This has the
 effect of *preventing* inlining in arr's RHS, and causing
 'arr' to be inlined at every call site.
 
 This is an annoying gotcha when using RULES, but I don't see an
 easy fix.

Whats wrong with simply keeping track of all the functions used in the
LHS of a rule and if one of these functions appears in the RHS of a
definition add an implicate INLINE pragma.

PS: Have you had a chance to look at the rule in my "Generator" post the
the haskell mailing list.  The rule is being fired up but the compiler
is not optimizing as well as it could.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



RE: Rule question.

1999-07-08 Thread Simon Peyton-Jones

Kevin

Sorry it's taken me a long time to look at this.
Two things are going on here.

First thing


  module KevinB where

  data Arr ix el = Arr Int [(ix,el)] deriving Show

  replaceMany :: [(ix,el)] - Arr ix el - Arr ix el
  replaceMany = error "In Replace Many"

  {-# RULES 
 "rule1" forall f,l,a. replaceMany (map f l) a = replaceManyMap f l a 
   #-}

  replaceManyMap :: (v - (ix,el)) - [(ix,el)] - Arr ix el - Arr ix el
  replaceManyMap = error "In Replace Many Map"

  arr s l = let a = Arr s [] in
replaceMany l a

If you compile this, replaceMany will be inlined in arr's defn,
which means that anyone importing KevinB won't see the version
of arr that has replaceMany in it.  So 

module KevinA where
import KevinB 
arr2 s l = arr s (map (\(i,e)-(i+2,e)) l)

will not fire the rule.

Solution: add an INLINE pragma to 'arr'.   This has the
effect of *preventing* inlining in arr's RHS, and causing
'arr' to be inlined at every call site.

This is an annoying gotcha when using RULES, but I don't see an
easy fix.


Second thing
~~
But, as you discovered, it still doesn't work. Reason: GHC spots
that 'arr' always returns bottom, and therefore declines to put
an inlining in the interface file at all.  Optimising functions that
are guaranteed to diverege isn't much use.  If you make your
replace* things do something useful I think you'll find it will work.

Simon


 -Original Message-
 From: Kevin Atkinson 
 Sent: Thursday, July 01, 1999 6:13 PM
 To: Simon Peyton-Jones
 Cc: 'GHC users'
 Subject: Re: Rule question.
 
 
 Simon Peyton-Jones wrote:
  
  Hmm.  Your example relies on inlining 'arr' at its call site.
  My guess is that you aren't using -O.  In that case, there's no
  cross-module inlining, so 'arr' doesn't get inlined.
  
  Is that it?
 
 No:
 
 [kevina@kevins-linux Rules]$ make clean
 rm -f *.o *.hi
 [kevina@kevins-linux Rules]$ make
 ghc -c T2.hs -fglasgow-exts -O
 ghc: module version changed to 1; reason: no old .hi file
 ghc -c Main.hs -fglasgow-exts -O
 ghc: module version changed to 1; reason: no old .hi file
 rm -f main
 ghc -o main -fglasgow-exts -O Main.o T2.o
 [kevina@kevins-linux Rules]$ ./main
 
 Fail: In Replace Many
 
 An INLINE arr did not help either.
 
 -- 
 Kevin Atkinson
 [EMAIL PROTECTED]
 http://metalab.unc.edu/kevina/
 



RE: Calling Haskell from C

1999-07-08 Thread Simon Marlow


 But before you do that do a gdb -c core in the directory 
 ghc/lib/std/ to
 figure out what is really crashing.  My unlit might of been crashing
 because I had the header files for glibc2.0 but the binaries for
 glibc2.1 installed.  It could make a bit of a difference ;)

True - I thought it was slightly strange that I didn't encounter any unlit
problems when I compiled 4.02 on a glibc 2.1 system.  In fact the binary
distribution I put up doesn't have your patch, I think.

Cheers,
Simon