Hi all

I am trying to build a GUI for GHCi using "GHC as a library". See
http://haskell.org/haskellwiki/GHC/As_a_library .

One requirement is that the GUI is still responsive when executing code
using GHC.runStmt. Therefore I do:

   forkIO $ GHC.runStmt someStatement >> return()

While this works fine, it does give me one problem. How do I terminate a
call to runStmt prematurely? One would think that this would work:

   threadId <-forkIO $ GHC.runStmt someStatement >> return()
   ...
   killThread threadId

However, as runStmt also uses forkIO internally I am not killing the
thread that runs "someStatement" - actually nothing seems to happen when
executing the action "killThread threadId".

Anybody knows how to kill the thread running "someStatement"?

I have attached a more complete program which illustrates the problem
described above. I have only tested the program on Debian/Linux.


Greetings,

Mads Lindstrøm


module Main where

-- Compile with: ghc -package ghc-6.6 --make StopingRunStmt.hs

import qualified GHC
import qualified Outputable
import qualified Packages
import qualified PackageConfig
import DynFlags

import System.IO
import Control.Concurrent

path = "/usr/lib/ghc-6.6/"

main = do session <- initializeSession
          threadId <- forkIO $ GHC.runStmt session "let foo = do threadDelay 100000; putStrLn \"a\"; foo in foo" >> return ()
          threadDelay (10^6*1)
          putStrLn "Killing thread"
          killThread threadId -- the thread is not killed here. Only when the hole programs terminates, is the thresad killed.
          threadDelay (10^6*5)

initializeSession =
    do -- start a new interactive session using the path specified above
       session <- GHC.newSession GHC.Interactive (Just path)
       
       -- initialize the default packages
       dflags1 <- GHC.getSessionDynFlags session
       (dflags2, packageIds) <- Packages.initPackages dflags1
       GHC.setSessionDynFlags session dflags2{GHC.hscTarget=GHC.HscInterpreted}
       
       -- now the order of the statements is important:
       -- 1) load our modified prelude functions
       target <- GHC.guessTarget "MyPrelude.hs" Nothing
       GHC.addTarget session target
       -- this would unload the standard prelude if it had already been loaded
       GHC.load session GHC.LoadAllTargets
       
       -- 2) load the standard prelude
       let preludeModule  = GHC.mkModule (PackageConfig.stringToPackageId "base") (GHC.mkModuleName "Prelude")
       controlConcurrentModule <- GHC.findModule session (GHC.mkModuleName "Control.Concurrent") Nothing
       GHC.setContext session [] [preludeModule, controlConcurrentModule]
       
       -- 3) replace "putStrLn" and "getLine" with our modified versions
       -- replaceFunctions session
       return session

_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to