Re: how to determine a programs memory usage at runtime?

2004-06-22 Thread Bernard James POPE
On Tue, Jun 22, 2004 at 09:27:40AM +0100, Simon Marlow wrote:
 On 22 June 2004 03:51, Bernard James POPE wrote:
 
  The mblocks_allocated variable should give me what I want.
  
  I think having access to this would also be useful to people who are
  profiling their programs. You see a few papers where people want to
  report how much memory their application needs, and having a
  high-water mark is usually good enough. Beats trying to get the
  information from top. 
 
 Note that this only counts memory allocated by the GHC storage manager;
 it doesn't include the data segments, malloc(), the C stack, or other
 mmap()'d stuff.  Be careful if your program is using any of these other
 allocation methods (perhaps via an external library through the FFI).

Ah, that's a good point. I didn't think of that.

For what it is worth I've put a simple Haskell wrapper to mblocks_allocated
on the web. It provides this function:

   megaBytesAllocated :: IO Integer

On my simple tests it seems reliable, when compared to what top says.

I've put it here in case anyone wants to use it:

   http://www.cs.mu.oz.au/~bjpop/code.html

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


Re: can you block a thread in GHC by its threadID?

2004-06-22 Thread Bernard James POPE
On Tue, Jun 22, 2004 at 10:37:54AM +0200, Volker Stolz wrote:
 In local.glasgow-haskell-users, you wrote:
  Ideally I'd like this function:
 blockThread :: ThreadId - IO ()
 unBlockThread :: ThreadId - IO ()
 
 I should have some bit-rotted patches here for
 freezeThread :: ThreadId - IO ()
 thawThread   :: ThreadId - IO () and a new PrimOp which
 allows you to set the next thread to run (at a first glance, at least
 I could find the patch for the latter).

If you could find them that would be great.

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


Re: can you block a thread in GHC by its threadID?

2004-06-22 Thread Bernard James POPE
On Tue, Jun 22, 2004 at 09:45:48AM +0100, Simon Marlow wrote:
 On 22 June 2004 06:11, Bernard James POPE wrote:
 
  Ideally I'd like this function:
  
 blockThread :: ThreadId - IO ()
  
  and thus:
  
 unBlockThread :: ThreadId - IO ()
 
 Hmm, might be possible.  Can the blocked thread be woken up by an
 exception?  (this is usually the case for blocked threads).

I guess so.

 Note that if you block a thread and then drop all references to it, the
 garbage collector will wake up the thread with a BlockedOnDeadMVar
 exception.

That sounds reasonable.

 I think I'd be tempted to call these functions {stop,continue}Thread to
 avoid overloading the block/unblock terms any more.  Stop/continue is
 used in Unix land too.

Yes, those names are fine (I was thinking of suspend/resume).

 To implement this you'll need another StgTSOBlockReason state for
 stopped threads.  Stopping already blocked threads might not be a
 problem, since (in some cases at least) the blocking operation will be
 retried when the thread is started again.  I'm not sure whether this is
 always the case though.  
 Stopping a thread blocked on a foreign call
 cannot be done.  Stopping a thread blocked on I/O or delay# will need to
 remove the thread from the appropriate queue.
 
 You'll need two new primops: stopThread#, continueThread#.  Take a look
 at the implementation of killThread# for clues (in
 ghc/rts/Exception.hc).  Don't forget to take into account the case when
 a thread stops itself (that's the tricky one).  

Hmm. In the worst case I can just ban it by comparing the
threadIds, and require the use of yield?

 Let us know if you need any more guidance...

Thanks. I'll start looking into it in more detail.

Supposing that such a thing is indeed possible is there any chance that
it could be folded into GHC? (Then I wouldn't have to ship my own variant
of the runtime with buddha.)

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


how to determine a programs memory usage at runtime?

2004-06-21 Thread Bernard James POPE
Hi all,

Is there any way I can find out or estimate the memory size
of a program while it is executing?

This may very well be problematic and system specific, but 
I haven't a clue where to look. Perhaps there is a posix
interface I am missing? Or a hook into the runtime?

Why do I want to know this?

I'm experimenting with interleaving the execution of
buddha's debugging algorithm with the execution of the
debuggee. Assume for the moment that the debuggee runs
in one thread and the debugger runs in another.

One strategy I want to test is running the debuggee until
some threshold of memory has been used, suspend the
debuggee and jump to the debugger, then possibly back again.

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


Re: how to determine a programs memory usage at runtime?

2004-06-21 Thread Bernard James POPE
On Mon, Jun 21, 2004 at 02:50:39PM +0100, Simon Marlow wrote:
 On 21 June 2004 09:14, John Meacham wrote:
 
  There might be some RTS calls to query the heap, but someone else is
  probably more qualified to comment on that.
 
 The value of the mblocks_allocated variable in the RTS will give you the
 number of megablocks currently mmap()ed into the address space of the
 executable, which roughly equates to the amount of memory the program is
 using.  A megablock is MBLOCK_SIZE bytes, currently 1Mb.
 
 Megablocks are never released, so this only gives you an upper limit for
 the amount of memory in use.
 

Thanks John and Simon,

The mblocks_allocated variable should give me what I want.

I think having access to this would also be useful to people who are
profiling their programs. You see a few papers where people want to report
how much memory their application needs, and having a high-water mark is
usually good enough. Beats trying to get the information from top.

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Thu, Apr 15, 2004 at 10:43:22AM -0700, Carl Witty wrote:
   However, if you have any suggestions about how to make a FAST 
   global counter
   I would be very glad to hear it. From profiling it seems like 
   this code
   is a little expensive (also it is called quite frequently).
  
  You could try the FastMutInt module from GHC
  (ghc/compiler/utils/FastMutInt.hs) to speed things up.  Unfortunately
  unsafePerformIO has some unavoidable overhead: it can't be inlined
  because we don't want the compiler to see its definition.
 
 What happens if you use the FFI to call a C function like
 int getCount() { static int x; return x++; }
 and mark the function pure (outside the IO monad) and noinline? 
 (Probably all the calls get commoned up and it only gets called once;
 but it might be worth a try).

Hi all,

To test out the various possible ways of implementing a global counter
I wrote some test cases (shown below). I hope the test cases are
useful, and provide some indication of the relative performance.
However, if you spot something bogus please let me know.

Each program computes the equivalent of:

sum ([1..1] :: [Int]) 

There are four different ways that I tried:

   1) pure: this is just pure functional code and should be fast. 
  This test case is only here as a control example, it is not
  a candidate solution because I need a global counter.
 
   2) ioref: this uses a global mutable counter using IORefs and
  unsafePerformIO

   3) fastMut: this uses the fast mutable integer library from GHC
  that was suggested by Simon Marlow.

   4) ffi: this implements the counter in C using the FFI.

They all run in a reasonable amount of memory so I won't report the
memory information here, just total runtime, as computed by the
unix time command.

Results:

   method  runtime (s)
   ---
   pure0.7
   ffi 3.2
   fastMut 15
   ioref   23  

Note each program was compiled with ghc 6.2 with -O2 on debian linux.

One caveat is that the ffi code keeps the counter in C until the very end
of the program. This doesn't reflect the fact that I want to put each
value of the counter into a Haskell data structure, so there should be
an additional cost of turning the C int back into a Haskell Int for every
increment. I'll need to write a different test case for this aspect.

Here are the programs in the same order that they appear in the results table:



   {- pure -}

   module Main where

   main = print $ loop 1 0

   loop :: Int - Int - Int
   loop 0 acc = acc
   loop n acc = loop (n-1) $! (acc + n)



   /* ffi Haskell code */ 

   {-# OPTIONS -fglasgow-exts #-}

   module Main where

   -- the use of unsafe makes a big difference in runtime
   foreign import ccall unsafe incC inc :: Int - ()
   foreign import ccall getCounterC getCounter :: Int - IO Int

   printCounter :: IO ()
   printCounter
  = do val - getCounter 0 -- the 0 is bogus
   print val

   main :: IO ()
   main = seq (loop 1) printCounter

   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)

   /* ffi C code */

   #include inc.h

   int counter = 0;

   void incC (int howmuch)
   {
  counter+=howmuch;
   }

   int getCounterC (int bogus)
   {
  return counter;
   }
 


   {- fastMut -}

   module Main where

   import System.IO.Unsafe (unsafePerformIO)
   import FastMutInt

   {-# NOINLINE counter #-}
   counter :: FastMutInt
   counter = unsafePerformIO newFastMutInt

   {-# NOINLINE inc #-}
   inc :: Int - ()
   inc n = unsafePerformIO $
  do incFastMutIntBy counter n
 return ()

   printCounter :: IO ()
   printCounter
  = do val - readFastMutInt counter
   print val

   main :: IO ()
   main = do writeFastMutInt counter 0
 seq (loop 1) printCounter

   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)



   {- ioref -}

   module Main where
   
   import System.IO.Unsafe (unsafePerformIO)
   import Data.IORef (newIORef, readIORef, writeIORef, IORef)
   
   counter :: IORef Int
   {-# NOINLINE counter #-}
   counter = unsafePerformIO (newIORef 0)
   
   {-# NOINLINE inc #-}
   inc :: Int - ()
   inc n = unsafePerformIO $
  do old - readIORef counter
 writeIORef counter $! old + n
   
   printCounter :: IO ()
   printCounter
  = do val - readIORef counter
   print val
   
   main :: IO ()
   main = seq (loop 1) printCounter
   
   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)  


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
Hi Andre,

 There's another way which you missed: using implicit parameters.  I 
 remember reading a paper a while ago called Global Variables in Haskell 
 (sorry, don't remember the author -- Jones, perhaps?) which did similar 
 benchmarking to yours, and carrying around the global variable with an 
 implicit parameter was faster than using a global mutable counter via 
 unsafePerformIO $ newIORef 

Thanks for the note. That was in the paper by John Hughes. The
performance difference between unsafePerformIO and implicit parameters
is not significant in his test case. I think he was surprised that 
implicit parameters worked so well (I am too). 

That doesn't mean I should rule it out completely. I'll have a look into
it.

Also, implicit parameters are less convenient for the program transformation
that I use in buddha, whereas a truly global variable is ideal.

On the other hand the FFI approach looks a lot faster already, and Simon
has suggested that I can inline unsafePerformIO.

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Tue, Apr 20, 2004 at 02:56:36PM +0200, Ketil Malde wrote:
 Bernard James POPE [EMAIL PROTECTED] writes:
 
  Note each program was compiled with ghc 6.2 with -O2 on debian linux.
 :
main = print $ loop 1 0
 
 Isn't this going to be optimized away to a constant with -O2?

Here's the final stg code, obtained by:

   ghc -ddump-stg -O2 --make MainPure.hs -o pure

 STG syntax: 
Main.$wloop =
\r [ww ww1]
case ww of ds {
  __DEFAULT -
  case +# [ww1 ds] of sat_s2pI {
__DEFAULT -
case -# [ds 1] of sat_s2pE {
  __DEFAULT - Main.$wloop sat_s2pE sat_s2pI;
};
  };
  0 - ww1;
};
SRT(Main.$wloop): []
Main.loop =
\r [w w1]
case w of w2 {
  GHC.Base.I# ww -
  case w1 of w3 {
GHC.Base.I# ww1 -
case Main.$wloop ww ww1 of ww2 { __DEFAULT - GHC.Base.I# [ww2]; };
  };
};
SRT(Main.loop): []
Main.eta =
\u []
case Main.$wloop 1 0 of ww {
  __DEFAULT - GHC.Base.I# [ww];
};
SRT(Main.eta): []
Main.lvl =
\u srt:(0,*bitmap*) []
case Main.eta of w {
  GHC.Base.I# ww - GHC.Show.$wshowSignedInt 0 ww GHC.Base.[];
};
SRT(Main.lvl): [Main.eta]
Main.main =
\r srt:(0,*bitmap*) [s]
case GHC.IO.hGetLine GHC.Handle.stdin s of wild {
  GHC.Prim.(#,#) new_s a41 -
  case GHC.IO.hPutStr GHC.Handle.stdout Main.lvl new_s of wild1 {
GHC.Prim.(#,#) new_s1 a411 -
GHC.IO.$whPutChar GHC.Handle.stdout '\n' new_s1;
  };
};
SRT(Main.main): [GHC.Handle.stdout, GHC.IO.$whPutChar,
 GHC.IO.hPutStr, GHC.Handle.stdin, GHC.IO.hGetLine, Main.lvl]
:Main.main =
\r srt:(0,*bitmap*) [eta1]
catch# [Main.main GHC.TopHandler.topHandler eta1];
SRT(:Main.main): [Main.main, GHC.TopHandler.topHandler]

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Tue, Apr 20, 2004 at 01:59:33PM +0100, Simon Marlow wrote:
 On 20 April 2004 12:48, Bernard James POPE wrote:
 
  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).

The time for fastMut with unsafePerformIO inlined is:

   3.6 sec

The code is below. Note I dropped the NOINLINE pragmas on counter and inc.
This was necessary to get the fast time (is this safe?, it gives the right
answer here but ...). Also I removed the constant 1 from the code 
(though it doesn't make any difference).

Thanks to all who have chipped in.

Cheers,
Bernie.



{-# OPTIONS -fglasgow-exts #-}
module Main where

import GHC.IOBase hiding (unsafePerformIO)
import FastMutInt
import GHC.Base

counter :: FastMutInt
counter = unsafePerformIO newFastMutInt

inc :: Int - ()
inc n = unsafePerformIO $
   do incFastMutIntBy counter n
  return ()

printCounter :: IO ()
printCounter
   = do val - readFastMutInt counter
print val

main :: IO ()
main = do line - getLine
  writeFastMutInt counter 0
  seq (loop (read line)) printCounter

loop :: Int - ()
loop 0 = ()
loop n = seq (inc n) (loop $! n - 1)

{-# INLINE unsafePerformIO #-}
unsafePerformIO :: IO a - a
unsafePerformIO (IO m) = case m realWorld# of (# _, r #) - r
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: turn off let floating

2004-04-14 Thread Bernard James POPE
On Tue, Apr 13, 2004 at 02:03:21PM +0100, Simon Marlow wrote:
  
  On Fri, Apr 09, 2004 at 03:27:01PM +0200, David Sabel wrote:
  
   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.
  
  That is exactly what I'm doing at the moment. The module that has the
  nasty impure bits in it is not compiled with optimisations. 
  I will improve this when GHC regains the non-let floating flag.
 
 If you need -ffull-laziness to force a certain behaviour when using
 unsafePerformIO, I say that what you're doing is at the very least
 unsupported ;-)  However, there are occasoinally good uses for this:
 HOOD is one; I imagine your case is similar?

Hi Simon,

What I am trying to do is implement a global (mutable) integer counter.
I'm using a combination of IORefs and unsafePerformIO.

The reason I want to do this is that I'm experimenting with a new 
design of buddha. Each function call in a program being debugged gets a 
new number by reading and incrementing the global counter. 

Thus the counter is read and incremented from within pure code 
(no IO monad).

Of course this is not what you are supposed to do in a pure language :)
Nonetheless, a global mutable counter is exactly what I want for this
job - I don't want to thread anything through the code.

So I have code like:

   {-# NOINLINE count #-}
   count :: IORef Int
   count = unsafePerformIO $ newIORef 0

   {-# NOINLINE getCount #-}
   getCount :: (Int - a) - a
   getCount f
  = let nextCount
 = (unsafePerformIO $
  do oldCount - readIORef count
 let newCount = oldCount + 1
 writeIORef count newCount
 return oldCount)
in seq nextCount (f nextCount)

It seems to work okay.

However, if you have any suggestions about how to make a FAST global counter
I would be very glad to hear it. From profiling it seems like this code
is a little expensive (also it is called quite frequently).

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


Re: turn off let floating

2004-04-10 Thread Bernard James POPE
On Fri, Apr 09, 2004 at 03:27:01PM +0200, David Sabel wrote:

 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.

That is exactly what I'm doing at the moment. The module that has the
nasty impure bits in it is not compiled with optimisations. 
I will improve this when GHC regains the non-let floating flag.

 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)

That is a possibility, but the code is part of buddha, my debugger.
I would have to require the user of buddha also to have HasFuse.

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


turn off let floating

2004-04-06 Thread Bernard James POPE
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


Re: turn off let floating

2004-04-06 Thread Bernard James POPE
On Tue, Apr 06, 2004 at 09:38:38AM +0100, Simon Peyton-Jones wrote:
 Strangely (and bogusly) there is no such flag in GHC6.2.  Someone must
 have noticed this already because it's there in the HEAD
 (-fno-full-laziness), and has been since Feb 2004.  Strange.

Thanks,

I think it would be good for the docs for System.IO.Unsafe
(in future releases that have this flag) to mention the actual flag name.

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


Re: Talking with the compiler

2004-01-20 Thread Bernard James POPE
Peter wrote:

 BTW, does Language.Haskell.Parser.parseModule already perform infix
 resolution? 

Unless it changed very recently, then no.

I have written some code for this very task:

   http://www.cs.mu.oz.au/~bjpop/code/Infix.hs

You give it the infix rules that are in scope and a module and it 
returns the module with the infix applications resolved. (Of course
knowing what rules are in scope is another story, not solved by this
piece of code).

Perhaps it is of some use to you?

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


a library for reifying values in GHC

2003-08-15 Thread Bernard James POPE
Hi all,

During my work on buddha (haskell debugger) I've had the need
to print arbitrary values from a running program.

Along the way I've written some code that works with GHC
to do this.

Just in case there are others who might benefit from this,
I've ripped some code out of buddha and made it into somewhat of
a library.

You can download it from here:

   http://www.cs.mu.oz.au/~bjpop/code.html

The main parts are:

   reify :: a - IO Graph
   data Graph = ...
   prettyGraph :: Graph - String 

The graph type is an ordinary data type:

   type Unique = Int   -- a unique label for each node
   type Tag = Int  -- what kind of node it is
   type NumKids = Int  -- how many children it has

   data Graph
  = AppNode Unique String Tag NumKids [Graph]  
  | CharNode Char
  | IntNode Int
  | IntegerNode Integer
  | FloatNode Float
  | DoubleNode Double
  | NullNode
  deriving Show

The main features are:

   - it is conservative wrt to evaluation (lazy). It does not
 make its argument evaluate any further,
   - it detects cycles in the heap representation and makes them
 visible in the Graph representation (though the current
 pretty printer does not take advantage of this), 
   - it knows about some special things like exceptions and
 some other oddities,
   - it ought to work on GHC 5 and 6, though I haven't tested it
 extensively on the latter

Functions are a sore point (they all get mapped to the one thing, sigh).

It makes use of the FFI and the nice API that GHC provides for the
RTS (is that enough TLAs in one sentence?)

Unfortunately to use the library you must compile with -prof. The reason
is to trick GHC into keeping names of data constructors on the heap.
I'd rather avoid this, and perhaps with the new HsDebug stuff in GHC there
is a better way to get such names, but I haven't looked too hard.
(Any ideas?)

An example is below.

Ooroo,
Bernie.



Here's an example:

   {- demonstrating the use of ReifyHs.reify -}
   
   module Main where
   
   import ReifyHs (reify)
   import PrettyGraph (prettyGraph)
   import Data.Char (toUpper)
   
   main :: IO ()
   main
  = do putStrLn $ GHC version:  ++ show __GLASGOW_HASKELL__
   let listTups = zip abcdefghij [1..]
   putStr \n\nForce the list to be evaluated a bit:\n\n
   print $ take 3 listTups
   graph - reify listTups
   putStr \n\nhere's the graph representation: \n\n
   print graph
   putStr \n\nhere's a pretty print of the above: \n\n
   putStrLn $ prettyGraph graph
   putStr \n\nForce the list to be evaluated a bit more:\n\n
   print $ take 5 listTups
   graph - reify listTups
   putStr \n\nthe graph pretty printed again: \n\n
   putStrLn $ prettyGraph graph



Running the example after make

   [EMAIL PROTECTED]:/tmp/reify$ ./test 
   GHC version: 504
   
   
   Force the list to be evaluated a bit:
   
   [('a',1),('b',2),('c',3)]
   
   
   here's the graph representation: 
   
   AppNode 1076636796 : 1 2 [AppNode 1076636776 (,) 1 2 [CharNode 'a',
   IntNode 1],AppNode 1076637368 : 1 2 [AppNode 1076637348 (,) 1 2 
   [CharNode 'b',IntNode 2],AppNode 1076637932 : 1 2 [AppNode 1076637912 
   (,) 1 2 [CharNode 'c',IntNode 3],AppNode (-1)  3 0 [
   
   
   here's a pretty print of the above: 
   
   [('a',1),('b',2),('c',3) .. ?
   
   
   Force the list to be evaluated a bit more:
   
   [('a',1),('b',2),('c',3),('d',4),('e',5)]
   
   
   the graph pretty printed again: 
   
   [('a',1),('b',2),('c',3),('d',4),('e',5) .. ?


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


signal handling and optimisation

2003-06-20 Thread Bernard James POPE
Hi All,

I'm trying to write some code that catches unix signals and turns them
into GHC exceptions, GHC version 6.0, debian linux

Heres my code:

--
   module Main where
   
   import Control.Concurrent
   import Control.Exception
   import System.Posix
   import IO 
   
   catchCtrlC :: IO Handler
   catchCtrlC
  = do main_thread - myThreadId
   installHandler sigINT (Catch (handler main_thread)) Nothing
   where
   handler :: ThreadId - IO ()
   handler main_thread = throwTo main_thread (ErrorCall Kaboom)
   
   main :: IO ()
   main = do catchCtrlC 
 print (f 1)
   
   f :: Int - Int
   f x = f (x + 1)
--   

The function f is intentionally bogus, I want it to loop so I have enough
time to hit cntrl-C.

When I compile this with no optimisations:

   ghc --make Sig.hs

I get the desired behaviour, that is soon after I hit cntrl-C I get:

   Fail: Kaboom

However, when I compile with -O:

   touch Sig.hs  ghc --make -O Sig.hs

Now the exception does not appear to be caught. Indeed the program just keeps
on looping.

If a give the program a lot of cntrl-Cs then eventually I get this message:

   a.out: too many pending signals

And the program dies.

Commenting out the call to catchCtrlC from within main seems to
let GHC's default signal handling mechanism work properly, that is
after (strangley 2) cntrl-Cs the program dies (no message). 

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


identifying a raise_closure from C

2003-02-24 Thread Bernard James POPE
Hi all,

In C, I have an StgClosure pointer, pointing to a THUNK.

I would like to know whether this particular THUNK is a raise_closure,
(as built by raisezh_fast() in rts/Exception.hc).

Is there any identifying information I can use to tell definitely whether
this THUNK is a raise_closure? Perhaps the stg_raise_info info table
has enough information?

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


Re: re-opening a closed stdin?

2002-11-20 Thread Bernard James POPE
Simon Marlow writes:
 I've been thinking about duplicating/replacing Handles for a while.
 Here's  a possible interface:
 
   -- |Returns a duplicate of the original handle, with its own buffer
   -- and file pointer.  The original handle's buffer is flushed,
 including
   -- discarding any input data, before the handle is duplicated.
   hDuplicate :: Handle - IO Handle
   -- |Makes the second handle a duplicate of the first handle.  The
   -- second handle will be closed first, if it is not already.
   hDuplicateTo :: Handle - Handle - IO ()

I'm not too sure of the issues here. Some examples that use them would be
helpful. 

The only suggestion I'd make is that the names be something with handle in
them:

   huDupHandle, hDupHandleTo

 The remaining questions are:
  - Should you be allowed to duplicate a Handle which refers
to a file opened in WriteMode?  Haskell 98 forbids having
two Handles pointing to the same file opened for writing,
but IMHO it's quite a reasonable thing to do.  If we don't allow
this, then there needs to be another version of hDuplicateTo
which invalidates the original Handle.

Why does Haskell 98 make this restriction (I don't think that the library
report says why)?

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



RE: replacing the Prelude (again)

2002-07-15 Thread Bernard James POPE

Hi All,

Thanks to everyone for their comments. 

I can see that this is quite a difficult design problem, and it is
unlikely that one solution will please everyone, which makes me think
that the current solution will probably stand.

Simon Peyton-Jones writes:

 Bernie writes:
 | anymore. What I would like is that the defualting rules refer 
 | to the classes in my version of the Prelude, 
 | not the Standard Prelude.
 
 You can always get that (with the -fno-implicit-prelude thing) by adding
 
   default [Int, Double]
 
 or whatever to your source module, just after the import that gets your
 new standard Prelude.  Doesn't that do it?  

I'll get back to you on this soon.

 It would also not be hard to arrange that the default default
 declaration became scoped with -fno-implicit-prelude (like fromInteger), if 
 that was useful.   

That sounds a lot like what I would like to have, but I'm probably
being selfish here.

 It's a good point; I thought that *all* the numeric
 stuff was un-coupled from the Prelude with -fno-implicit-prelude, 
 but it isn't quite.

What I would like to know is the semantics of -fno-implicit-prelude with
respect to this bit from the Haskell Report:

   4.3.4  Ambiguous Types, and Defaults for Overloaded Numeric Operations

   Ambiguities in the class Num are most common, so Haskell provides another 
   way to resolve them---with a default declaration:
   default (t1 , ... , tn)
   where n=0, and each ti must be a monotype for which Num ti holds. 
  ^^
   In situations where an ambiguous type is discovered, an ambiguous type 
   variable is defaultable if at least one of its classes is a numeric class 
   (that is, Num or a subclass of Num) and if all of its classes are defined 
^
   in the Prelude or a standard library 
  ^
   Each defaultable variable is replaced by the first type in the default list 
   that is an instance of all the ambiguous variable's classes. It is a 
   static error if no such type is found.

Do these become whatever Num is in scope when I use -fno-implicit-prelude,
and whatever classes from standard libraries are in scope? If they don't
then I think I'm in a pickle.

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



Re: replacing the Prelude (again)

2002-07-15 Thread Bernard James POPE

Hi again,

Malcolm writes:
 We came across the same problem in the Hat tracer (which is also a
 source-to-source transformation, and can also be used for debugging).
 
 The problem is that the transformation introduces new classes, so
 Prelude.Ord - HatPrelude.Ord
 Prelude.Eq  - HatPrelude.Eq
 Prelude.Num - HatPrelude.Num
 
 The defaulting mechanism *only* applies to types constrained by
 the original builtin Prelude.Num, not to the transformed class
 HatPrelude.Num.

I did wonder how Hat tackled this.

Out of curiosity what is the solution that Hat uses? And what is
the situation in nhc98?

 I think you are saying that if we
 import HatPrelude as Prelude
 together with -fno-implicit-prelude in GHC, then defaulting should work
 over the HatPrelude classes rather than the Prelude ones?

That's what I had hoped for. 

 Unfortunately, in Hat at least, we continue to use the original
 Prelude in *addition* to the replacement HatPrelude.  

This adds an extra element of difficulty to the problem. I am trying
my hardest to avoid needing the to import the original Prelude in 
a transformed module - this requires quite a bit of desugaring in the
transformation. Still, I would like to be able to use do notation and
have it refer to Prelude.Monad, not MyPrelude.Monad. I can live without
it of course.

For what reasons do you require the original prelude? 

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



Re: replacing the Prelude (again)

2002-07-15 Thread Bernard James POPE

Malcolm writes:
 Bernie writes: 
  I did wonder how Hat tackled this.
  Out of curiosity what is the solution that Hat uses?
 
 Hat doesn't have a solution.  When the lack of correct defaulting
 causes Hat to generate type-incorrect code, the underlying compiler
 will complain vociferously.  Our advice to users is to write `default
 ()' at the top of the module, then resolve the type errors they
 get from the normal compilation so that defaulting is completely
 eliminated.  The code will then go through Hat smoothly.
 
 It isn't very satisfactory, but in practice, defaulting doesn't
 really occur very often, so it isn't too much of a hardship.

That was going to be my fallback strategy, I'm glad I'm not the only one!

  This adds an extra element of difficulty to the problem. I am trying
  my hardest to avoid needing the to import the original Prelude in 
  a transformed module - this requires quite a bit of desugaring in the
  transformation. 
  
  For what reasons do you require the original prelude? 
 
 Exactly the same reasons.  We want to do as little desugaring as
 necessary in the transformation, so inevitably we need at least a
 small part of the Prelude in scope.

I would like to use do-notation in the transformed program, but have it
refer to Prelude.Monad and not MyPrelude.Monad which is also in scope.

The reason I mention this is that the behviour of -fno-implicit-prelude seems to
have changed with respect to desugaring do notation, at least according to
this post from Simon Peyton-Jones:
  
   http://www.haskell.org/pipermail/glasgow-haskell-users/2002-July/003688.html

   In the upcoming 5.04 release you'll be able to do exactly
   that.  GHC will use whatever = is in scope if you say
   -fno-implicit-prelude.

Sure I can always get by without do notation, but the transformed program is
then a lot uglier and harder to comprehend. 

Does hat work with ghc 5.04?

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



announce: StableTable Printer for GHC

2002-05-01 Thread Bernard James POPE

Hi all,

Ever had that deep desire to see what was in that pesky
Stable Pointer/Name table?

Probably not, but I did, and I wrote some code to
print it out in all its glory from the safe confines
of a Haskell program. I thought I'd share it with you
just in case one day you too want to see what is lurking in
there.

You can find the code here:

   http://www.cs.mu.oz.au/~bjpop/code.html 

Here's an example of what it can do:

-

  module Main where

  import Stable
  foreign import ccall printStableTable printStableTable :: IO ()

  main = do let list = [1,2,3,4] ++ list
print $ take 5 list
trueSName - makeStableName True
listSPtr1   - newStablePtr list
listSPtr2   - newStablePtr list
printStableTable

If you run this program, you get as output:

   [1,2,3,4,1]
   --- Begin Stable Table ---
   
   stable_ptr_free = 3
   
   0.val= NULL
   0.ref= 0
   0.sn_obj = NULL
   
   1.val= (addr = 0x80963e0) True
   1.ref= 0
   1.sn_obj = STABLE_NAME
   
   2.val= (addr = 0x500c11c4) (: 1 (: 2 (: 3 (: 4 cycle
   2.ref= 2
   2.sn_obj = NULL
   
   3.val= free at pos 4
   3.ref= 0
   3.sn_obj = NULL
   
   4.val= free at pos 5
   4.ref= 0
   4.sn_obj = NULL
   
   ... blah blah blah, until the end of the table ...

-

Some features:

   It shows each entry in the table, and implicitly the
   free list, starting at stable_ptr_free.

   Data structures are printed in all their glory, 
   including the current address of the value and
   the representation of the value. 

   Cycles are detected! (See 2.val), but other types
   of sharing are not yet shown, however it is possible
   with tweaks.

Why might you want this?

1. Debugging the stable pointer table implementation.

2. Debugging your own code.
   Stable pointers introduce the potential for nasty
   space leaks in Haskell programs. Much like malloc/free
   in C. If you forget to free your pointers then the 
   space is retained. If you suspect that your program
   is leaking space in this way, then just whip out the
   table printer and see what is looks like.

3. Checking how much sharing you have in your data (with
   tweaks, as I said ealier you can show sharing).

What do you need to use it?

   Just a current version of GHC. It should compile out of
   the box without any modification to GHC.

   Oh, and you have to compile your program with -prof to
   see all the data constructors.

How does it print the data structures with cycles?

   The library also comes with yet another library for
   prinitng arbitrary Haskell Data structures, done
   via the FFI interface.

   NOTE: this is different from the GHCinternals library.

   We can detect cycles more easily if we are just 
   printing things and not building new values on the heap
   at the same time. Probably this extra library should live
   somewhere by itself, but I have just bundled them together
   at the moment.

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



Re: getting types out

2002-04-10 Thread Bernard James POPE

 I know -ddump-types will get me the types of top level functions, but is
 there a way to get ghc (or really any compiler) to dump the types of
 everything (or at least more than that, maybe just locally bound
 definitions)?

Hi Hal,

I once tried to do this with an older version of GHC. From memory it
was kind-of possible with a little bit of hacking the ghc type
checking code.

What I was able to do was dump type schemes for top-bound and
let/where bound identifiers. 

It is tricky to know what to do with free variables in the scheme,
I don't think I did anything special with them.

Simon Peyton Jones asked me if I wanted to add this feature to
ghc, but I never got around to doing this, mostly because I got
distracted by other things.

In my spare time I (and a few colleagues) have been adding a parser
and other trimmings to Mark Jones' Typing Haskell in Haskell code.
Its not released and not finished, mainly due to time constraints.
The main lacking feature is multi-module programs, in particular
module interface code (partly done but not complete). However it
works enough for what I want to do. I have been thinking for a long
time that I would like to release it to others, but I have been
held back because it is incomplete and I would like some better
documentation. Also I haven't asked Mark for his permission. I also
think there are other people who are doing similar things, but we never
really communicated properly, which is a shame, I think the Haskell
Communities project should help in this respect.

My main goal with this code was to have a stand-alone tool for Haskell
that would provide detailed information about the static aspects of
a program: types, kinds, class hierarchies, identifier definitions,
binding groups and so on.

One wonders whether a better option would be to pull the front off an
existing Haskell implementation. I tried to do this with ghc, nhc and
also hugs, without success for various reasons.

It is hard to get money and Haskell programmers to work on such
projects, and so it is relegated to a spare time hobby.

I know this doesn't really answer your question, but I did once ask
the same thing... 

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



Re: ghc 5.02.2 FFI question

2002-04-09 Thread Bernard James POPE

Hi Simon,

(posted to [EMAIL PROTECTED] in case anyone else is
reading this).

 I just tried your example and it seems to run in constant space here
 with 5.02.2.  The code looks fine - this isn't something we really
 envisaged people doing with the RTS API, but there's no real problem
 with it except that of course you don't get the benefits of type
 checking.  I'm sure you have very good reasons for building Haskell
 expressions in C :-)

My motivation is debugging. I was trying to implement a similar interface
to the HugsInternals one. I succeeded except the I noticed what looked to
me like a space leak, so I simplified the program a bit.

 Can you give us any more clues?  What were the symptoms when you ran it?

Okay, I've simplified the program even more. Now I just have a program that
calls a C function to build a Double, and then passes a stable pointer
back to it.

For comparison, I also made it possible to avoid calling C, ie just build
a Double in Haskell and make a stable pointer reference to it in Haskell.

My intuition, which maybe very wrong, is that the two ways of executing
should have very similar memory profiles and time performance. They run
in about the same time. Both processes grow bigger over time (as you will
see below), but the one that calls C grows much much faster. I'm presuming
that I can rely on the unix program 'top' to give me reasonably good
results.

First the code, then the profiles:

The Haskell code.



   module Main where

   import Foreign

   -- returns a stable pointer to a Double (489.0923)
   foreign import leak leak :: IO (StablePtr Double)

   -- change to callLeak' to compare behaviour
   main = do repeatIO 50 callLeak

   -- call into C to make a Double
   callLeak :: IO ()
   callLeak = do doubleSPtr - leak
 doubleVal  - deRefStablePtr doubleSPtr
 freeStablePtr doubleSPtr
 print doubleVal


   -- don't call into C
   callLeak' :: IO ()
   callLeak' = do doubleSPtr - newStablePtr (489.0923::Double)
  doubleVal  - deRefStablePtr doubleSPtr
  freeStablePtr doubleSPtr
  print doubleVal



The C code:



   #include /home/bjpop/ghc-5.02.2/ghc/includes/Rts.h
   #include /home/bjpop/ghc-5.02.2/ghc/includes/RtsAPI.h
   #include LeakC.h

   StgStablePtr leak (void)
   {
   StgClosure *num;
   num = rts_mkDouble(489.0923);
   return (getStablePtr ((StgPtr)(num)));
   }



Okay, now for the tests:

If I compile the program so that it calls to C via the FFI 
then this is what top gives me over 30 second samples:

SIZE RSS  TIME
--
1708 1708 0:00
2748 2748 0:30
3772 3772 1:00
4788 4788 1:30
5828 5828 2:00
6812 6812 2:30

The process is definitely growing in size, and it looks linear.



If I compile the program so that it does not call C
(by modifying the definition of main so that it uses callLeak')
then this is what top gives over 30 second samples:

SIZE RSS  TIME
--
1692 1692 0:00
1704 1704 0:30
1720 1720 1:00
1736 1736 1:30
1752 1752 2:00
1764 1764 2:30

The process is still growing, but very slowly. I wouldn't expect
it to grow at all, but I don't know the memory management of
ghc well enough to be sure.



I thought I should look at the output from the garbage collector to see
if anything obvious came up. The verbose mode of '+RTS -S -RTS' spat out
lots of stuff as you would guess. I can post a snippet to you if it is of
interest, but I'll wait to see what you say.

The not-verbose output is as follows:



When calling C:

   2,460,833,948 bytes allocated in the heap
 1,911,280 bytes copied during GC
26,192 bytes maximum residency (1 sample(s))
   
  7500 collections in generation 0 (  1.79s)
 1 collections in generation 1 (  0.00s)
   
 1 Mb total memory in use
   
 INIT  time0.01s  (  0.00s elapsed)
 MUT   time  160.84s  (410.71s elapsed)
 GCtime1.79s  (  3.94s elapsed)
 EXIT  time0.00s  (  0.00s elapsed)
 Total time  162.64s  (414.65s elapsed)
   
 %GC time   1.1%  (1.0% elapsed)
   
 Alloc rate15,298,936 bytes per MUT second
   
 Productivity  98.9% of total user, 38.8% of total elapsed



When not calling C:

   2,454,983,980 bytes allocated in the heap
 1,911,300 bytes copied 

Re: rts/Printer.c

2002-03-18 Thread Bernard James POPE

  If it's a global symbol, you should be able to access it form the ffi.
  
  If you want to traverse data structures the way you can using the
  HugsInternals library, you might want to tweak the code a little to
  provide a similar semantics/ API.  Basically, all you have to do is
  take the C code and split it into handy bits.
 
 This is a nice idea - we'll be happy to incorporate the changes.

Hi,

I'm on to it.

Let's presume for the moment that I will solve a simpler problem,
before I get the full task done.

Say, for argument's sake, that I want to make the function
printObj() available in Haskell, where:

   void printObj (StgClosure *obj);

(as defined in and exported from rts/Printer.c)

In Haskell I want to reflect this as:

   printObj :: a - IO ()

Alistair mentioned that I could use the FFI to access some C code
in the RTS.

My intuition would have been to go about adding a primop as described in
/ghc/compiler/prelude/primops.txt (ie without calling through the FFI).

My trouble is I can't find any examples that are greatly similar to what
I want to do.

My question is: should I implement it through the FFI or as a primitive
ala primops.txt? Perhaps they amount to much the same thing.

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



RE: adding isWHNF primop to 5.00.2 native code generator

2001-08-03 Thread Bernard James POPE

Hi all,

Hack alert!

I took Julian's advice and looked over the assembly output from
ghc.

In all the cases I tried, the info pointer in the closure header
pointed to the end of the info table. Although a comment in
ghc/includes/ClosureMacros.h worries me:

   info pointerThe first word of the closure.  Might point
 to either the end or the beginning of the
 info table, depending on whether we're using
 the mini interpretter or not.  GET_INFO(c)
 retrieves the info pointer of a closure.

Can someone please clarify when the info pointer will point to
the beginning or end of the table?

Basically I have assumed for the moment that it points to the end
of the table, as that is what some other code in ghc seems to 
assume.

This makes it easy (hack?) to find the type field of the info table,
its just the bottom (or top, depending on which way you look at it)
16 bits prior to the address that the info pointer contains. Essentially
dataToTag# gives you these bits. I don't think dataToTag# is a great
name for this primop, something like: closureType#, or classifyClosure#
might be better.

My current strategy is to simply compare the type field with 
the constants from ClosureTypes.h, using the Haskellised names 
re-exported from SMRep.lhs as suggested by Simon Marlow.

My problem is that this is a dodgy assumption since the design of the 
info table may change in the future, and you get a nasty 
unchecked dependency between the primops in the NCG and the design
of the rts. 

It seems hard to get the kind of automatic offset calculation in the 
NCG as you get with the C version of primops. My current idea
is to make some C primops that do the structure and array indexing
for me, and then use them in the NCG. i.e. primops that essentially
export 'closure_flags[type]' and 'get_itbl(c)-type' to the NCG.

Does anyone know of a better solution?

In any case I am happy for the moment with my hacky solution, since it
gives the right results and it is what I need to write up my
paper.

Cheers,
Bernie.

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



RE: help needed for adding isWHNF primop to 5.00.2

2001-07-31 Thread Bernard James POPE

Hi all,

Apologies for my large number of postings to this list of late.

 the normal definition of WHNF applies only
 to types containing _|_, i.e. pointed types.  Unpointed types are never
 represented by thunks, so I would be inclined to include them in WHNF.

Yes, I agree here. It is useful for me since I am using WHNF to determine
whether expressions are evaluated. Perhaps it is a slight abuse of the
terminology, but it gives me what I want :)

 You also have to deal with indirections, although you can assume (at the
 moment) that an indirection will eventually lead to an object in WHNF.

Good point. I did make this assumption. Well to be precise I made the
assumption that the thunk and indirection closure flags were mututally
exclusive. If things change I guess I will have to follow the indirections.

currently my definition is:

   #define isHNFzh(r,a) r=(! closure_THUNK((StgClosure *)a))

I believe under this definition that unpointed types and indirections 
are considered to be in WHNF. My initial tests seem to indicate that
this is working well. 

 You have to declare the primitive like this,
 BTW:
 
   isWHNF# :: a - (# State# RealWorld, Int# #)
 
 because the compiler doesn't know about the IO type and you can't return
 a Bool directly.

I'm not too fussed about the unboxed Int, although as Marcin points out
it does look like some of the comparision primops can return a Bool. 
I couldn't figure out how they did it so I left it with the Int#.

 There's no problem with the simplifier as long as you declare the
 primitive to have the correct properties, i.e. that the polymorphic
 argument is lazy.

Great.

 It sounds like you also need a way to take apart arbitrary objects and
 look at their components.  

Yes indeed. I use type classes for this with deriving rules for user 
defined types. 
I'm in the midst of writing this up for IFL, in Stockholm, mid September. 
In particular, I am looking for portable ways of taking objects
apart, that's why type classes are attractive. Of course, isWHNF
cannot be written in Haskell, but if I can get it to work for Hugs,
GHC and NHC, then that is good enough for me :) 

What I hope is that some of this can appear as a Meta-programming
library for Haskell, which is more powerful than Read and Show. 
Something a bit similar to the semantic domain of Meta-ML.

 I know that Andy Gill was also interested in
 having similar facilities, perhaps he can help out.

I wonder if Andy is reading this? Possibly there are other people
around who are also interested in this. I think the HAT people
at NHC headquarters are also interested in these things. There 
once was talk of starting a debugging group for Haskell, but I
don't know what happened.

Thanks heaps for your help.

Bernie.

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



Re: help needed for adding isWHNF primop to 5.00.2

2001-07-30 Thread Bernard James POPE

 |  I would like to add a primitive to GHC 5.00.2 of the form:
 | 
 | isWHNF :: a - Bool
 
 One might be inclined to ask what for?  Such a primitive is
 probably difficult to implement, given the variety of GHC's
 closures, 

From reading the documentation that comes with GHC and glancing over the
source code, I came to these set of assumptions, please correct me if I am
wrong:

- values of unpointed types are never in WHNF

- values of pointed types may be in WHNF, in particular:

 - data constructors are in WHNF
 - partial applications are in WHNF
 - functions are in WHNF
 - thunks are not in WHNF
   (this list is probably not exhaustive as you say, but I am happy
with this set of definitions for the moment)

 and is potentially dangerous -- you could conceivably
 break referential transparency (?)  

With the type that I have specified above, yes, it is _very dangerous_
when used without caution. I do not intend for this feature to be
used widely in everyday programming. Its probably not terribly useful for
most tasks either.

 I can also imagine it
 could interact badly with the complexities of GHC's 
 simplifer.

This is something I do not know. In the end I may define it with this type:

   isWHNF :: a - IO Bool 

as Simon Marlow suggested, indeed this was my original intention, but I am new 
to the internals of GHC and thought it might be easier to get the unsafe one 
working first. For my own purposes the unsafe version is what I want. 
However, the version in the IO monad looks more reasonable, and I can get
the unsafe version with unsafePerformIO, whilst maybe requiring some 
pragmas to help the simplifier out?

 What would you hope to gain from such a thing?  Perhaps
 you have some wider purpose which could be achieved some 
 other way?

I want it for the purposes of meta-programming, and also for debugging since
that is what I am working on. At the end of a computation (that results in
a value of pointed type, say) I want to know to what extent expressions were
evaluated:

  foo xs = take 3 xs

  ... foo [4..] ...

   debugger foo [4,5,6,_ = [4,5,6]

Since I am inspecting things after the computation is complete, I should
be able to rely on the information from isWHNF.

I don't think that the scheme that HOOD uses is right for me, since 
the overheads would be too costly (I don't want to log every reduction in
my program just in case I might need to debug a branch of the
computation later on). 

If you like, what I am doing is a post-mortem inspection of (some) values 
generated by a program. This is quite standard for declarative debuggers
for non-strict languages.

I can do this in HUGS via the HugsInternals interface, and I think that it
is also possible in NHC too. 

I'm eager to hear you comments and suggestions, and I appreciate the
feedback that I have received so far. 

Cheers,
Bernie.

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



types from ghc - got them!

2000-11-20 Thread Bernard James POPE

Hi again,

For my previous example:

   main = putStr $ show (fred 1 3)
where
fred a b = let myid x = x in myid (plus a b) 
plus x y = x + y 

I can now get the following output:

    Bernie: All Binder TypeSigs 
   main :: IO ()
   plus :: forall a. (Num a) = a - a - a
   fred :: forall a. (Num a) = a - a - a
   myid :: forall t_aMv. t_aMv - t_aMv

Which is exactly what I want. Turned out to be quite simple in the end.

Thanks a lot for all your help Simon.

Just out of curiosity, do you think that this sort of output would be
useful for other people? I don't know what your plans are for GHCi, but you
may be considering a mode that prints types out, something like :t in
hugs. I always found it frustrating in hugs that I couldn't get the types
of locally defined values. My students also find this frustrating, and it
sometimes causes them to avoid local definitions. Obviously there are issues
with type variables which are quantified outside the local definition, but
careful naming of things should be able to fix this.

Regards,
Bernie.


Simon Peyton-Jones writes:

 Bernie
 
 All (I think) the top level bindings come out of the type check
 as an AbsBinds.  This is where we generalise from a monomorphic
 thing to a polymorphic thing.
 
 An AbsBinds has four components, the third of which is a list of
 triples (TyVar, Id, Id).  You want to grab the first of these Ids (only).
 You can then ignore the MonoBinds inside the fourth component of
 the AbsBinds.  So your code will get quite a bit simpler.
 
 The two Ids in the triple are the polymorphic top-level binder and
 the monomorphic (perhaps recursive) thing that it generalises.
 It's a bit hard to explain in a short space.  Look at the output of the 
 desugarer for a simple defn, to see what an AbsBinds translates to.
 
 Anyway these polymorphic Ids will have exactly the for-alls and
 constraints that you want
 
 hope this gets you moving

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



types from ghc (another question)

2000-11-18 Thread Bernard James POPE

Hi again,

Simon Peyton-Jones writes:

 Don't try to get the type environment out.  Instead, look at the
 syntax tree produced by the type checker.  Each binder is an Id.
 There's a function
 idType :: Id - Type
 that tells you the type of each binder.  Quite how you present it
 to the user in a good way isn't clear to me,

Thanks Simon.

In TcModule.lhs I added some code like this:

   myDumpTc results 
 = myPprMonoBinds $ tc_binds results
 where
 myPprMonoBinds (AndMonoBinds b1 b2) 
= myPprMonoBinds b1 $$ myPprMonoBinds b2
   
 myPprMonoBinds (FunMonoBind id _ matches _) 
= (ppr (toRdrName id)) + 
  dcolon + 
  (ppr $ idType id) $$ 
  myPprMatches matches 

   {- etc, etc ... -}
   
   
For the following contrived example:
   
   main = putStr $ show (fred 1 3)
where
fred a b = let myid x = x in myid (plus a b) 
plus x y = x + y 
   
My output is:

   main :: IO ()
   plus :: a - a - a
   fred :: a - a - a
   myid :: t_aMv - t_aMv

Which is nearly exactly what I want, however, the class constraints are missing
from the signatures for plus and fred. The universal quantification of 
the type variable t_aMv is also missing.

One curiosity is that the compiler has generated the variable 'a' in
the two circumstances where the variables are constrained, which makes me think
something special is happening here.

If you defined all the binders at the top-level and supplied the
-ddump-types flag to ghc (with a modification to the code to turn off the 
conversion to HsType, so that the unique variable names do not get clobbered) 
you get the proper polymorphic type signatures
for each of the identifiers (ie myid :: forall t_aMv . t_aMv - t_aMv).

My question is: can I find out any information about the constraints on
variables from the types that I find in the tc_binds component of the type
checking results?

(apologies for my being long-winded).

Regards,
Bernie.

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



getting type information about local bindings

2000-11-09 Thread Bernard James POPE

Hi all,

In GHC 4.09 the flag "-ddump-types" causes the type signatures of 
top-level bound identifiers to be printed.

I would really like to make use of the type-checker in GHC, however, I would
also like to obtain the types of locally bound identifiers
(things in let expressions and where clauses). Obviously there is going to
be some trickery regarding type variables from enclosing scopes.

I looked in the TcModule.lhs module and noticed that the TcResults 
value returned by typecheckModule contains a value environment that only
specifies the types of top bound identifiers.

Further investigation of the code led me to the TcBinds.lhs module
and the tcBindsAndThen function. I can see that local type environments 
are not passed upwards during type checking/inference.

At some point I got lost in the code. Does anyone know of a reasonable means
for obtaining this type information? I don't mind doing some hacking, but
I wanted to get advise from the experts as to whether I might be wasting
my time. 

Perhaps such a thing is done somewhere when generating Core code?

As an aside I dare say that such an extension would be useful to other 
people, particularly those writing source transformation code.

Regards,
Bernie.

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