Simon Marlow wrote:
> > But I (and maybe others) don't like mail filters that file
> > away mailing lists. I prefer to have everything in a single
> > inbox and visual "scan" it myself. Therefore, a short tag
> > is actually quite useful - but it should be short (that was
> > my point).
>
> I v
> But I (and maybe others) don't like mail filters that file
> away mailing lists. I prefer to have everything in a single
> inbox and visual "scan" it myself. Therefore, a short tag
> is actually quite useful - but it should be short (that was
> my point).
I vote not to add a short tag to the
Thomas Hallgren <[EMAIL PROTECTED]> wrote,
> "Manuel M. T. Chakravarty" wrote:
>
> > Some mail readers have a summary
> > mode that shows only some 20 characters of the subject line.
>
> For this reason, I think you should not add a tag at
> all. I don't think this is necessary. The presence of
"Manuel M. T. Chakravarty" wrote:
> Some mail readers have a summary
> mode that shows only some 20 characters of the subject line.
>
> Manuel
For this reason, I think you should not add a tag at all. I don't think this is
necessary. The presence of "glasgow-haskell-users" in the To: or CC: fiel
Barbara Nostrand <[EMAIL PROTECTED]> wrote,
> The reason to add something like HASKELL: to the beginning of subject lines
> is that it makes it easier for humans to scan in boxes for Haskell related
> stuff. Granted, I can generally tell when a message relates to Haskell, but
> I subscribe to a n
>
> Sven writes:
>
> > P.S.: Something completely unrelated: Why is majordomo.haskell.org
> > expanded to scarlet.cam.uk.eu.microsoft.com in the To:-field?
> > IMHO this is a bad idea, e.g. when people cut-and-paste this
> > into their address books and scarlet is renamed to
>
Simon Peyton-Jones wrote:
> [...]
> foreign export dynamic
> mkFooCB :: (Int -> Int -> IO ()) -> IO Addr
>
> freeHaskellFunctionPtr :: Addr -> IO ()
>
> Now if you want the callback itself to free itself, you say
>
> do {
> a <- fixIO (\a -> mkFooCB (callBack a))
Hi.
The reason to add something like HASKELL: to the beginning of subject lines
is that it makes it easier for humans to scan in boxes for Haskell related
stuff. Granted, I can generally tell when a message relates to Haskell, but
I subscribe to a number of mailing lists where the identity of the
;t that enough?
Simon
> -Original Message-
> From: Sven Panne [mailto:[EMAIL PROTECTED]]
> Sent: Tuesday, April 13, 1999 10:09 AM
> To: GHC Users
> Subject: Re: Q: Threads in GHC's RTS
>
>
> "Sigbjorn Finne (Intl Vendor)" wrote:
> > [...]Good poi
Sven writes:
> P.S.: Something completely unrelated: Why is majordomo.haskell.org
> expanded to scarlet.cam.uk.eu.microsoft.com in the To:-field?
> IMHO this is a bad idea, e.g. when people cut-and-paste this
> into their address books and scarlet is renamed to e.g. rhett. :-)
"Sigbjorn Finne (Intl Vendor)" wrote:
> [...]Good point, I've committed a fix for this.
Adjustor.c gets more and more impressive. :-) BTW: What is the
schedule for porting (i.e. completely rewriting) Adjustor.c to
non-Intel platforms?
> If I understand your scenario right, that only leaves g
Yes, you cannot reliably free 'yourself' when using the C calling
convention and "foreign export dynamic". Good point, I've committed
a fix for this.
If I understand your scenario right, that only leaves getting at
the address of the old-Haskell-callback-to-be-nuked, but it's
reachable without t
Alas, the saga continues: After a thinking a little bit more about
Simon's and Sigbjorn's replies to my question, I'm now convinced that
it is not as simple as it seems, because there are *two* kinds of pointers
in this game. Again my scenario, this time a little bit more verbose:
1. Create a
Sven Panne <[EMAIL PROTECTED]> wrote,
> "Manuel M. T. Chakravarty" wrote:
> > [...]
> > The required synchronization could of course be programmed
> > using `Concurrent's semaphores, but with the disadvantage
> > that if we want to provide this thread-safety transparently
> > for user application
> One other thing: since unsafePerformIO already has a NOINLINE
> pragma on it,
> I don't think it's necessary to explicitly NOINLINE all these
> top-level
> mutable thingies.
Oh yes it is:
foo :: IORef Int
foo = unsafePerformIO (newIORef 0)
baz :: IO Int
baz = do { v <- readIORef foo;
To follow up on Sergey's suggestion a while back,
let's keep this within Haskell98 realms and use
{-# notInline ... #-}
instead. (This is not supported in 4.02, but
ghc-current has got it).
--sigbjorn
> Simon Marlow [mailto:[EMAIL PROTECTED]] writes:
>
>
> > That's what you get with unsa
> That's what you get with unsafePerformIO; we've even
> added a {-# NOINLINE blockingSem #-} pragma for exactly this reason.
> (Doubtless undocumented.)
ahem. Quote from the 4.02 documentation at
http://research.microsoft.com/users/t-simonm/ghc/Docs/latest/users_guide/use
rs_guide-4.html#ss4.2
> Yes, we do this a lot. It's such a useful thing
> that I wonder whether we should support it more directly,
> somehow. As it stands, its vulnerable to 'blockingSem'
> getting inlined at its usage sites, which would be a total
> disaster. That's what you get with unsafePerformIO; we've even
>
Sven Panne <[EMAIL PROTECTED]> writes:
>
[...]
>
> Aaaah! *lights going on* But then I suggest that foreign export
> dynamic should be changed to return a stable pointer instead
> of an Addr. This shouldn't break too much code, because both
> are CCallable.
>
I don't see the need, since
Simon Peyton-Jones wrote:
> Yes, we do this a lot. It's such a useful thing that I wonder
> whether we should support it more directly, somehow.
That eases my mind. :-) I feared that I'm the only one doing this
kind of hackery...
> As it stands, its vulnerable to 'blockingSem' getting inlin
> I'm not sure if this is neccessary, because it is possible to have
> global (mutable!) variables via IORefs + unsafePerformIO:
>
> blockingSem :: IORef QSem
> blockingSem = unsafePerformIO (newIORef =<< newQSem 1)
>
> gtkMumbleFooBar :: ... -> IO ()
> gtkMumbleFooBar ... = do
>...
>wai
"Manuel M. T. Chakravarty" wrote:
> [...]
> The required synchronization could of course be programmed
> using `Concurrent's semaphores, but with the disadvantage
> that if we want to provide this thread-safety transparently
> for user applications in a library, we have to define a
> "new" IO mona
Dear GHC Gurus ;-)
Michael Hobbs <[EMAIL PROTECTED]> and I were just discussing
the use of GHC's threads (ie, the `Concurrent' library)
within GTK+ applications when we came across an
inconsistency between ``The STG runtime system (revised)''
and the actual implementation of the RTS in GHC 4.02.
23 matches
Mail list logo