Sigh, this time with an attachement..

----- Original Message ----- 
From: "Sigbjorn Finne" <[EMAIL PROTECTED]>
To: "Simon Peyton-Jones" <[EMAIL PROTECTED]>
Cc: <[EMAIL PROTECTED]>; <[EMAIL PROTECTED]>;
<[EMAIL PROTECTED]>
Sent: Monday, June 23, 2003 12:53
Subject: Re: GHCi bug - the impossible happened loading FranTk with ghc-6.0
on Win32


> I tidied up this aspect of TclHaskell / FranTk as part of a Galois
> project a while ago. Attached are the as-is changes needed to
> avoid being dependent on RTS internals & stop doing a busy wait.
> In addition to these diffs, you also want to comment out the defn of
> isOnlyProcess in  TclCompatibilityGhcSupportsConcurrency.hs
>
> hth
> --sigbjorn
>
> ----- Original Message ----- 
> From: "Simon Peyton-Jones" <[EMAIL PROTECTED]>
> To: "GHC bugs" <[EMAIL PROTECTED]>;
<[EMAIL PROTECTED]>
> Cc: "Meurig Sage" <[EMAIL PROTECTED]>
> Sent: Monday, June 23, 2003 02:32
> Subject: RE: GHCi bug - the impossible happened loading FranTk with
ghc-6.0
> on Win32
>
>
> > Simon
> >
> > The underlying problem is that no one is maintaining FranTk at the
> > moment.  Perhaps you'd like to?
> >
> > Anyway, FranTk seems to use an un-documented (and therefore unreliable)
> > hook into GHC's RTS.  When you use GHCi to load systems that link to RTS
> > hooks, the dynamic linker's symbol table must be initialised to include
> > those symbols.  So the 'solution' here is to add 'run_queue_hd' to the
> > RTS_SYMBOLS in ghc/rts/Linker.c.  You'll need to build GHC from source
> > do to this.
> >
> > Longer term, it'd be a good plan to see just what FranTk wants to know
> > here, and what API the RTS should expose to support it.
> >
> > Admittedly, ghci dies with a rather unhelpful message
> >
> > Simon
> >
> >
> > | -----Original Message-----
> > | From: Meurig Sage [mailto:[EMAIL PROTECTED]
> > | Sent: 12 June 2003 16:26
> > | To: Simon Peyton-Jones
> > | Cc: Meurig Sage
> > | Subject: Re: GHCi bug - the impossible happened loading FranTk with
> > ghc-6.0 on Win32
> > |
> > | Hi Simon
> > |
> > ...
> > |
> > | That being said as far as I remember:
> > | FranTk contains the following function which attempts to check whether
> > there
> > | are any other threads waiting to be scheduled. If there are none then
> > it
> > | blocks waiting for more user input events, if there are any then it
> > simply
> > | queries the user input event queue and returns immediately. This makes
> > use
> > | of a variable run_queue_hd exported by Schedule.h (I think) in the ghc
> > | run-time system. When I was working on this in ghc-5.0x ghc compiled
> > ghc
> > | code provided access to this variable but ghc-i did not. Not sure what
> > Simon
> > | Marlow has done to this since.
> > |
> > | Hope this helps
> > |
> > | The function that does the check is the following one in
> > | FranTk/TclHaskellSrc/TclCompatibilityGhcSupportsConcurrency.hs.
> > |
> > |
> > | isOnlyProcess :: IO Bool
> > | isOnlyProcess = fmap toBool $ _casm_ ``%r = run_queue_hd ==
> > END_TSO_QUEUE;''
> > |  where
> > |   toBool :: Int -> Bool
> > |   toBool 0 = False
> > |   toBool _ = True
> > |
> > | Meurig
> > |
> > | ----- Original Message -----
> > | From: "Simon Peyton-Jones" <[EMAIL PROTECTED]>
> > | To: "Meurig Sage" <[EMAIL PROTECTED]>
> > | Sent: Thursday, June 12, 2003 2:13 PM
> > | Subject: FW: GHCi bug - the impossible happened loading FranTk with
> > ghc-6.0
> > | on Win32
> > |
> > |
> > | Hi Meurig
> > |
> > | Are you still around?  Do you remember what the issue is here?  We
> > | havn't the foggiest idea
> > |
> > | Simon
> > |
> > | -----Original Message-----
> > | From: [EMAIL PROTECTED]
> > | [mailto:[EMAIL PROTECTED] On Behalf Of Guest,
> > | Simon
> > | Sent: 12 June 2003 09:12
> > | To: [EMAIL PROTECTED]
> > | Subject: GHCi bug - the impossible happened loading FranTk with
> > ghc-6.0
> > | on Win32
> > |
> > | I can use FranTk with GHC-6.0 on Windows XP just fine in some
> > | configurations.
> > | It's OK when compiling with GHC.  It's also OK with GHCi when using
> > | FranTk with no concurrency.
> > |
> > | However, when trying to load a concurrency enabled FranTk into GHCi, I
> > | get "the impossible happened".
> > |
> > | I tried the workaround for the other GHCi bug, but this apparently
> > | different, as shown below.
> > |
> > | Full disclosure requires me to highlight the following text from the
> > | FranTk makefile:
> > |
> > | # Ununcomment this line to support concurrency.
> > | # This support does NOT work with ghci. It does not currently export
> > | # the special run_head_queue variable. Will allegedly
> > | # be fixed in a future version of ghc.
> > |
> > | # this version supports concurrency
> > | SUPPORTCONCURRENCY = TclCompatibilityGhcSupportsConcurrency.hs
> > |
> > | Is it simply that this hasn't been fixed yet?  (I'm not sure what
> > | symptoms are "expected".)
> > | I'd very much like to be able to use FranTk with concurrency.  Any
> > | chance of a fix?
> > |
> > | cheers,
> > | Simon
> > |
> > | ------------
> > | sjg-pc$ ghci
> > |    ___         ___ _
> > |   / _ \ /\  /\/ __(_)
> > |  / /_\// /_/ / /  | |      GHC Interactive, version 6.0, for Haskell
> > 98.
> > | / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
> > | \____/\/ /_/\____/|_|      Type :? for help.
> > |
> > | Loading package base ... linking ... done.
> > | Loading package lang ... linking ... done.
> > | Loading package text ... linking ... done.
> > | Prelude> :t GHC.Err.error
> > | GHC.Err.error :: forall a. [Char] -> a
> > | Prelude> :set -package FranTk
> > | Loading package concurrent ... linking ... done.
> > | Loading package haskell98 ... linking ... done.
> > | Loading package util ... linking ... done.
> > | Loading package data ... linking ... done.
> > | Loading package FranTk ... linking ...
> > | \\pinkgin\redrum_disk2\sjg\software\I686-~$5\ghc\latest\bin\ghc.exe:
> > | panic! (the `impossible' happened, GHC version 6.0):
> > |         can't load package `FranTk'
> > |
> > | Please report it as a compiler bug to
> > [EMAIL PROTECTED],
> > | or http://sourceforge.net/projects/ghc/.
> > |
> > | --
> > | Registered Office: Roke Manor Research Ltd, Siemens House, Oldbury,
> > | Bracknell,
> > | Berkshire. RG12 8FZ
> > |
>

Attachment: tclh.diff
Description: Binary data

Reply via email to