heap profiling and name truncation

2005-11-14 Thread Abraham Egnor
I'm trying to use the built-in ghc heap profiling and running into a
large roadblock: the names of producers are truncated, often into
uselessness, and there doesn't seem to be an option to control this. 
Am I missing something in the docs?

Abe
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: explicit signatures and default for integer literals

2005-05-31 Thread Abraham Egnor
Ghc can't assume "in this context" - the object file produced by
compilation could be linked into code that provides other instances.

Abe

On 5/31/05, Dinko Tenev <[EMAIL PROTECTED]> wrote:
> On 5/31/05, robert dockins <[EMAIL PROTECTED]> wrote:
> >
> > Dinko Tenev wrote:
> >
> > >
> > > First we observe that, g = new . flip zip [0..], so, without the type
> > > specification, it has the general type (New [(a, b1)] b, Num b1, Enum
> > > b1) => [a] -> b, as reported by GHC.
> > >
> > > Then we infer from
> > >
> > > (1) g :: (New [(u, v)] w, Num v, Enum v) => [u] -> w
> > >
> > > and
> > >
> > > (2) instance New [(a, b)] (Map a b)
> > >
> > > that in (New [(u, v)] w), w can only be (Map u v)
> >
> > This step in the reasoning requires a functional dependency, which you
> > mentioned earlier you were unwilling to supply.  Without functional
> > dependencies w can, in fact, be something other than (Map u v).
> 
> We need to infer New [(u, v)] w, and the only thing we know so far is
> New [(a, b)] (Map a b).  In this context, what else could we possibly
> have for w besides (Map u v) ?
> 
> Cheers,
> 
> D. Tenev
> ___
> 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


limited-scope retry?

2005-04-21 Thread Abraham Egnor
Suppose that a program using the Control.Concurrent.STM module had a
producer/consumer setup - one thread writing to a channel, the other
thread reading from the channel.  It seems natural to want a function
that the producer can call that will block until the consumer has
finished consuming everything currently in the channel.  The way I
first tried implementing this was:

-- types simplified for this example
flush :: TChan () -> STM ()
flush chan =
  do e <- isEmptyTChan
if not e then retry else return ()

Used in isolation, i.e.

atomically $ writeTChan chan ()
atomically $ flush chan

it works fine.  However, when composed (atomically $ writeTChan chan
() >> flush chan), it causes a race condition, usually resulting in
deadlock, as the "retry" in flush replays the call to writeTChan as
well.

This situation begs for a way to limit the scope of "retry", in which
case flush would be:

flush chan = limitRetry $
  do e <- isEmptyTChan
if not e then retry else return ()

Abe
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADTs and pedagogy was Re: GADTs and fundeps

2005-04-08 Thread Abraham Egnor
> > You mean, if the data type being defined doesn't actually use the
> > generality of GADTs, allow GADT syntax, and deriving() too?
> 
> Yes, that would be very nice for the HaskellDemo and new users.
> I'd definitely switch all of my non-GADT datatypes to use that.

One worry I have about this is that it'll introduce a new tripwire
that new users will have to watch out for - if they use GADT notation
for all data defintions, eventually they'll pass the threshold beyond
which deriving() mysteriously doesn't work, probably without even
knowing they're doing anything different.

Abe
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Scoped type variables

2004-12-17 Thread Abraham Egnor
Please!  I've lost count of the number of times when I've written code as

f :: a -> b
f (x :: a) = ...

wishing that I didn't have to locally bind the 'a'.

I'm not sure I understand the objection raised by Jon; the 'implicit
declaration' of type variables in type signatures has never bothered
me, and in fact seems quite similar to how names for values don't have
to be declared beforehand but are brought into scope by the binding
(which I also have no problem with).

Abe

On Fri, 17 Dec 2004 19:37:00 +, Keean Schupke
<[EMAIL PROTECTED]> wrote:
> what about having -fno-lexically-scoped-types for old code?
> 
> Keean.
> 
> Simon Peyton-Jones wrote:
> 
> >OK, OK, I yield!
> >
> >This message is about lexically scoped type variables.  I've gradually
> >become convinced that if you write
> >
> >   f :: [a] -> [a]
> >   f x = 
> >
> >then the type variable 'a' should be in scope in .   At present in
> >GHC you have to write
> >   f (x :: [a]) = 
> >to bring 'a' into scope.
> >
> >I've fought against this because it seems funny for a 'forall' in a type
> >signature to bring a type variable into scope in perhaps-distant
> >function body, but it's just so convenient and "natural".  Furthermore,
> >as Martin Sulzmann points out, you might have type variables that are
> >mentioned only in the context of the type:
> >   g :: Foo a b => [a] -> [a]
> >   g = ...
> >GHC provides no way to bring 'b' into scope at the moment, and that
> >seems bad design.
> >
> >
> >If I do this, which I'm inclined to, it could break some programs,
> >because (with -fglasgow-exts) all type signatures will bring scoped type
> >variables into scope in their function body.  Here's an example that
> >will break
> >
> >   f :: [a] -> [a]
> >   f x = my_id x
> >  where
> >  my_id :: a -> a
> >  my_id y = y
> >
> >The type signature for my_id will become monomorphic, since 'a' is now
> >in scope, so the application (my_id x) will fail saying
> >   can't unify 'a' with '[a]'.
> >In some ways that makes sense.  If you used 'b' instead in the defn of
> >my_id, it'd be fine, because my_id would get the type (forall b. b->b).
> >Fixing such breakages is easy.
> >
> >
> >So there it is.   Any one have strong opinions?  (This is in addition to
> >the existing mechanism for bringing scoped type variables into scope via
> >pattern type signatures, of course.)
> >
> >Simon
> >___
> >Glasgow-haskell-users mailing list
> >[EMAIL PROTECTED]
> >http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> >
> >
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bug in touchForeignPtr?

2004-11-22 Thread Abraham Egnor
> If finalizers are not the right thing, what else is?

I've found that when writing an interface to a C library that requires
resource management, it's much better to use the withX (see
Control.Exception.bracket) style of function than to use finalizers -
programs are much easier to reason about and debug.

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


overzealous defaulting?

2004-08-23 Thread Abraham Egnor
I'm not sure if this is an actual bug, as opposed to an odd instance
of defaulting:

*GUI.Parser> let printQ q = runQ q >>= print
*GUI.Parser> :t printQ
printQ :: forall a. (Show a) => Q a -> IO ()
*GUI.Parser> let p = printQ
*GUI.Parser> :t p
p :: Q Integer -> IO ()

...but I'm not sure when that would ever be the correct behavior.

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


Re: GHCI/FFI/GMP/Me madness

2004-08-09 Thread Abraham Egnor
Ah, that triggers the bug for me as well.  Oddly, calling
System.Mem.performGC once isn't enough, but twice is:

Ok, modules loaded: Main.
*Main> mpz_new
*Main> System.Mem.performGC
*Main> str_test
1

vs.

Ok, modules loaded: Main.
*Main> mpz_new
*Main> System.Mem.performGC
*Main> System.Mem.performGC
*Main> str_test
139406720

On Mon, 9 Aug 2004 19:36:37 +0200, Remi Turk <[EMAIL PROTECTED]> wrote:
> On Mon, Aug 09, 2004 at 01:09:40PM -0400, Abraham Egnor wrote:
> > FWIW, I couldn't reproduce this problem on my system (i.e. str_test
> > always printed "1").  GHC 6.2.1, libgmp 4.1.3, debian unstable
> >
> > Abe
> 
> Same versions here, on an old heavily-patched/FUBAR rock linux
> 1.4 system.
> 
> Does the following make any difference? (trying to cause GCing)
> 
> Haskell/Mpz/weird% make
> ghci util.o -#include util.h PrimMpz.hs
>___ ___ _
>   / _ \ /\  /\/ __(_)
>  / /_\// /_/ / /  | |  GHC Interactive, version 6.2.1, for Haskell 98.
> / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
> \/\/ /_/\/|_|  Type :? for help.
> 
> Loading package base ... linking ... done.
> Loading object (static) util.o ... done
> final link ... done
> Compiling Main ( PrimMpz.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> mpz_new
> *Main> sum (replicate (200*1000) 0)
> 0
> *Main> str_test
> 1076535944
> *Main>
> 
> Groeten,
> Remi
> 
> 
> 
> --
> Nobody can be exactly like me. Even I have trouble doing it.
>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-09 Thread Abraham Egnor
FWIW, I couldn't reproduce this problem on my system (i.e. str_test
always printed "1").  GHC 6.2.1, libgmp 4.1.3, debian unstable

Abe

On Mon, 9 Aug 2004 17:57:14 +0200, Remi Turk <[EMAIL PROTECTED]> wrote:
> On Sun, Aug 08, 2004 at 07:34:04AM -0700, Sigbjorn Finne wrote:
> > Hi,
> >
> > please be aware that the RTS uses GMP as well, and upon
> > initialisation it sets GMP's 'memory functions' to allocate memory
> > from the RTS' heap. So, in the code below, the global variable
> > 'p' will end up having components pointing into the heap.
> > Which is fine, until a GC occurs and the pointed-to
> > GMP allocated value is eventually stomped on by the storage
> > manager for some other purpose.
> >
> > I'm _guessing_ that's the reason for the behaviour you're seeing.
> 
> Hm, I _was_ aware of mp_set_memory_functions being used by the RTS.
> I've seen it often enough in ltrace's ;)
> It does indeed sound rather plausible (and making big allocations
> and such does indeed cause it to happen earlier).
> 
> At which point my next question is: what now? I don't feel really
> confident about my GHC-hacking skills (huh? skills? where? ;) so
> does that mean I'm out of luck?
> *looks* Am I correct that I'd have to copy any GMP-allocated
> memory to my own memory before returning from C and vice-versa?
> I hope not :(
> 
> Happy hacking,
> Remi "3212th unfinished project" Turk
> 
> 
> 
> --
> Nobody can be exactly like me. Even I have trouble doing it.
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


imports with --make?

2004-03-23 Thread Abraham Egnor
Is there any way to use --make but provide paths to search for .hi files,
*not* .hs files?  For example, if a library doesn't use ghc's package
system, and is distributed in precompiled form, there doesn't seem to
currently be a way to point ghc at the import files when using --make - it
always complains that it can't find the modules, and -v shows that it is
only looking for .hs files.

Abe

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


Re: Generics... no Tuples > 2 either...

2004-02-26 Thread Abraham Egnor
I've been frustrated by the same lack of instances; as a stopgap, here's
one for a three-tuple.  The pattern is pretty clear and can easily be
extended to whatever size you'd like.

tupCon = mkConstr 1 "(,,)" Prefix

instance (Data a, Data b, Data c) => Data (a, b ,c) where
gfoldl k z (a, b, c) = ((z (,,) `k` a) `k` b) `k` c
toConstr _ = tupCon
fromConstr _ = (undefined, undefined, undefined)
dataTypeOf _ = mkDataType [tupCon]

MR K P SCHUPKE <[EMAIL PROTECTED]> writes:
>
>Any chance of Data instances for tuples of size
>greater than 2... One of the nice things about generics is
>you can use them by deriving Data on your datatypes - of
>course this doesn't work if you all of a sudden have to 
>put a load of boiler-plate in just to use tuples...
>
>   Regards,
>   Keean Schupke
>___
>Glasgow-haskell-users mailing list
>[EMAIL PROTECTED]
>http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>



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


force garbage collection?

2003-10-05 Thread Abraham Egnor
Is there any way to force collection of all unreachable data structures?

Abe

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