Re: How to make Claessen's Refs Ord-able?

2002-03-21 Thread Koen Claessen


 | I'd like to extend the Ref type for observable sharing
 | of Koen Claessen's Ph.D. thesis: to make it possible
 | for the Refs to be the keys for efficient finite maps.

I did this in the Lava implementation. The Ref module I
attach works in Hugs and GHC.

/Koen.


module Ref
  ( Ref   -- * - * ; Eq, Show
  , ref   -- :: a - Ref a
  , deref -- :: Ref a - a
  , memoRef   -- :: (Ref a - b) - (Ref a - b)
  
  , TableIO   -- :: * - * - * ; Eq
  , tableIO   -- :: IO (TableIO a b)
  , extendIO  -- :: TableIO a b - Ref a - b - IO ()
  , findIO-- :: TableIO a b - Ref a - IO (Maybe b)
  , memoRefIO -- :: (Ref a - IO b) - (Ref a - IO b)

  , TableST   -- :: * - * - * - * ; Eq
  , tableST   -- :: ST (TableST s a b)
  , extendST  -- :: TableST s a b - Ref a - b - ST s ()
  , findST-- :: TableST s a b - Ref a - ST s (Maybe b)
  , memoRefST -- :: (Ref a - ST s b) - (Ref a - ST s b)
  )
 where

import MyST

import IOExts
  ( IORef
  , newIORef
  , readIORef
  , writeIORef
  , fixIO
  , unsafePerformIO
  )

import UnsafeCoerce
  ( unsafeCoerce
  )

{-

Warning! One should regard this module as a portable
extension to the Haskell language. It is not Haskell.

-}

{-

Here is how we implement Tables of Refs:

A Table is nothing but a unique tag, of type TableTag.
TableTag can be anything, as long as it is easy
to create new ones, and we can compare them for
equality. (I chose IORef ()).

So how do we store Refs in a Table? We do not
want the Tables keeping track of their Refs
(which would be disastrous when the table
becomes big, and we would not have any garbage
collection).

Instead, every Ref keeps track of the value it
has in each table it is in. This has the advantage
that we have a constant lookup time (if the number of
Tables we are using is small), and we get garbage
collection of table entries for free.

The disadvantage is that, since the types of the
Tables vary, the Ref has no idea what type of
values it is supposed to store. So we use dynamic
types.

A Ref is implemented as follows: it has two pieces
of information. The first one is an updatable
list of entries for each table it is a member in.
Since it is an updatable list, it is an IORef, which
we also use to compare two Refs. The second part is
just the value the Ref is pointing at (this can never
change anyway).

-}

-
-- Ref

data Ref a
  = Ref (IORef [(TableTag, Dyn)]) a

instance Eq (Ref a) where
  Ref r1 _ == Ref r2 _ = r1 == r2

instance Show a = Show (Ref a) where
  showsPrec _ (Ref _ a) = showChar '{' . shows a . showChar '}'

ref :: a - Ref a
ref a = unsafePerformIO $
  do r - newIORef []
 return (Ref r a)

deref :: Ref a - a
deref (Ref _ a) = a

-
-- Table IO

type TableTag
  = IORef ()

newtype TableIO a b
  = TableIO TableTag
 deriving Eq

tableIO :: IO (TableIO a b)
tableIO = TableIO `fmap` newIORef ()

findIO :: TableIO a b - Ref a - IO (Maybe b)
findIO (TableIO t) (Ref r _) =
  do list - readIORef r
 return (fromDyn `fmap` lookup t list)

extendIO :: TableIO a b - Ref a - b - IO ()
extendIO (TableIO t) (Ref r _) b =
  do list - readIORef r
 writeIORef r ((t,toDyn b) : filter ((/= t) . fst) list)

-
-- Table ST

newtype TableST s a b
  = TableST (TableIO a b)
 deriving Eq

tableST :: ST s (TableST s a b)
tableST = unsafeIOtoST (TableST `fmap` tableIO)

findST :: TableST s a b - Ref a - ST s (Maybe b)
findST (TableST tab) r = unsafeIOtoST (findIO tab r)

extendST :: TableST s a b - Ref a - b - ST s ()
extendST (TableST tab) r b = unsafeIOtoST (extendIO tab r b)

-
-- Memo

memoRef :: (Ref a - b) - (Ref a - b)
memoRef f = unsafePerformIO . memoRefIO (return . f)

memoRefIO :: (Ref a - IO b) - (Ref a - IO b)
memoRefIO f = unsafePerformIO $
  do tab - tableIO
 let f' r = do mb - findIO tab r
   case mb of
 Just b  - do return b
 Nothing - fixIO $ \b -
  do extendIO tab r b
 f r
 return f'

memoRefST :: (Ref a - ST s b) - (Ref a - ST s b)
memoRefST f = unsafePerformST $
  do tab - tableST
 let f' r = do mb - findST tab r
   case mb of
 Just b  - do return b
 Nothing - fixST $ \b -
  do extendST tab r b
 f r
 return f'

-
-- Dyn

data Dyn
  = Dyn

toDyn :: a - Dyn
toDyn = unsafeCoerce

fromDyn :: Dyn - a
fromDyn = unsafeCoerce


RE: Measuring memory usage of Glasgow Haskell programs

2002-03-21 Thread Simon Marlow


 Judging from the source (rts/Stats.c), the 10 Mb total memory in use
 figure here counts the number of megablocks allocated... but what does
 this actually mean?
 
 It's fairly straightforward to determine a program's maximum 
 stack size by
 fiddling with the -K runtime option and using a binary search.
 
 Is there a similarly easy way to find a program's maximum 
 heap size?  I
 don't think fiddling the -M option will work, because that affects the
 execution (it can cause extra GCs).

You can find an approximation to the maximum instantaneous resident data
size by switching to 2-space collection (+RTS -G1) and fixing the
allocation area size to some arbitrarily small value (eg. +RTS -A256k).
The program will take a long time to run, because it will do a major GC
every time the allocation area is full up.  You can decrease the run
time (and the accuracy) by increasing the size of the allocation area.
The stats output will then tell you both the maximum and average
residency of the program.

 And is there a way to measure static memory usage?  And then the
 maximum combination of stack+heap+static?  (I guess that is 
 the maximum
 residency above)?

The residency only takes into account heap-resident data, static data
isn't included.  I think the stack is excluded from this figure, though.

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



GHC for MacOS X: Success!

2002-03-21 Thread Wolfgang Thaller

After weeks of wrestling with Apple's buggy version of gdb, 
registerized compilation on MacOS X finally works!
I've tested it on GHC itself and on my own (H)OpenGL program, VOP, 
and it seems to work now.

I'm attaching my patches.

I've had trouble compiling the newest version from CVS. Instead, I've 
stayed behind by one week (13th of March, to be exact). Bootstrapping 
from the old ghc 5.00.2 binary version seems to work only up to 
around 4th of March (Binary IO doesn't work properly with GHC 
5.00.2/MacOS X).

If I find enough webspace, I'll upload a binary version, too, to save 
other people the work of recompiling GHC twice in a row.

Profiling doesn't work, I just get some segfaults. Is there anything 
specific that needs to be done to get profiling to work, or should I 
just go on another long bug-hunt?

So, Mac users, please try it out and tell me if it works for your 
programs, too!

Cheers,

Wolfgang


P.S. to Simon Marlow: You were right, those segfaults _are_ fun! Who 
would have thought that the PowerPC has so many registers that a 
clobbered callee-save only shows up _seconds_ later?
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



GHC for MacOS X: Success!

2002-03-21 Thread Wolfgang Thaller

I'm attaching my patches.

Well, I'm attaching them _now_.

Cheers,

Wolfgang


%ghc-5.03-macosx.patch.gz
Description: application/applefile


ghc-5.03-macosx.patch.gz
Description: Binary data