Thread-safe GHC

2015-08-31 Thread Corentin Dupont
Hello,
I am wondering if GHC itself is thread-safe.
I am using Hint, and it reports that GHC is not thread-safe, and that I
can't safely run two instances of the interpreter simultaneously.
Is that still the case?
Thanks!
Corentin



-- Forwarded message --
From: Daniel Gorín 
Date: Thu, Aug 27, 2015 at 5:09 PM
Subject: Re: Thread-safe Hint
To: Corentin Dupont 


Hi Corentin,

sorry for the late reply. Until relatively recently, the problem was still
on. But I too remember seeing something related to this issue being fixed
(iirc, the problem was the runtime linker, which used global state), so
perhaps it is already fixed in 7.10. If you can verify this, it shouldn’t
be hard to show the error message only on old versions of ghc. I’ll be away
for a couple of weeks, but if you want to look into this and send a patch,
I’ll merge it when I return.

Cheers,
Daniel

> On 24 Aug 2015, at 10:43 am, Corentin Dupont 
wrote:
>
> Hello Daniel,
> I noticed the following message in Hint:
> This version of GHC is not thread-safe,can't safely run two instances of
the interpreter simultaneously.
>
> Is it still the case with recent versions of GHC?
> It would be neat to be able to launch several instances of the
interpreter. In my game Nomyx I have several "match-up" going on and having
one instance of the interpreter would be nicer. Otherwise I am obliged to
reset the interpret each time I want to interpret something, which is time
consuming (2-3 seconds).
>
> Thanks,
> C
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Fwd: Thread-safe Hint

2015-08-28 Thread Corentin Dupont
Hello,
I am wondering if GHC is now thread-safe.
I am using Hint, and it reports that GHC is not thread-safe, and that I
can't safely run two instances of the interpreter simultaneously.
Is that still the case?
Thanks!
Corentin


-- Forwarded message --
From: Daniel Gorín 
Date: Thu, Aug 27, 2015 at 5:09 PM
Subject: Re: Thread-safe Hint
To: Corentin Dupont 


Hi Corentin,

sorry for the late reply. Until relatively recently, the problem was still
on. But I too remember seeing something related to this issue being fixed
(iirc, the problem was the runtime linker, which used global state), so
perhaps it is already fixed in 7.10. If you can verify this, it shouldn’t
be hard to show the error message only on old versions of ghc. I’ll be away
for a couple of weeks, but if you want to look into this and send a patch,
I’ll merge it when I return.

Cheers,
Daniel

> On 24 Aug 2015, at 10:43 am, Corentin Dupont 
wrote:
>
> Hello Daniel,
> I noticed the following message in Hint:
> This version of GHC is not thread-safe,can't safely run two instances of
the interpreter simultaneously.
>
> Is it still the case with recent versions of GHC?
> It would be neat to be able to launch several instances of the
interpreter. In my game Nomyx I have several "match-up" going on and having
one instance of the interpreter would be nicer. Otherwise I am obliged to
reset the interpret each time I want to interpret something, which is time
consuming (2-3 seconds).
>
> Thanks,
> C
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: No context in error messages

2014-09-09 Thread Corentin Dupont
Anyway, I think I figured it out:
Hint is using the Show instance of ErrMsg.
But it is defined only in term of errMsgShortString:

https://www.haskell.org/ghc/docs/7.6.3/html/libraries/ghc-7.6.3/src/ErrUtils.html#ErrMsg

So we are missing the context infos.



On Tue, Sep 9, 2014 at 12:01 AM, Corentin Dupont 
wrote:

> Hi everybody,
> I am working with Hint, after some discussion with Daniel Gorin, I decided
> to post here, I hope it's the right place.
> My problem with Hint is that I cannot get context in error messages while
> interpreting a string. If you run the attached file example.hs, you get:
>
> GhcError {errMsg = "No instance for (GHC.Num.Num GHC.Base.String)\n
> arising from a use of `GHC.Num.+'\nPossible fix:\n  add an instance
> declaration for (GHC.Num.Num GHC.Base.String)"}
>
> There is no context (line number, code snippets...), plus the error
> message uses fully qualified names, which is not very readable.
> It's very hard to figure out where the problem is when interpreting a long
> string.
> But the same error in a file that is loaded with Hint gives the correct
> message (uncomment the putStrLn in SomeModule.hs to get it):
>
> GhcError {errMsg = ":\n[1 of 1] Compiling
> SomeModule   ( SomeModule.hs, interpreted )"},GhcError {errMsg =
> "SomeModule.hs:5:22:\nNo instance for (Num String) arising from a use
> of `+'\nPossible fix: add an instance declaration for (Num String)\n
> In the second argument of `($)', namely `\"bar\" + 1'\nIn a stmt of a
> 'do' block: putStrLn $ \"bar\" + 1\nIn the expression:\n  do {
> putStrLn \"bar\";\n   putStrLn $ \"bar\" + 1 }"}
>
> This error is much better: it gives line number plus some code snippets
> ("In the second argument of...").
>
> There might be a flag that is not correctly set in GHC? After a quick look
> I'm thinking of GHC.DynFlags (I'm no expert). Now it is configured with:
> configureDynFlags :: GHC.DynFlags -> GHC.DynFlags
> configureDynFlags dflags = dflags{GHC.ghcMode= GHC.CompManager,
>   GHC.hscTarget  = GHC.HscInterpreted,
>   GHC.ghcLink= GHC.LinkInMemory,
>   GHC.verbosity  = 0}
>
> Thanks,
> Corentin
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


No context in error messages

2014-09-08 Thread Corentin Dupont
Hi everybody,
I am working with Hint, after some discussion with Daniel Gorin, I decided
to post here, I hope it's the right place.
My problem with Hint is that I cannot get context in error messages while
interpreting a string. If you run the attached file example.hs, you get:

GhcError {errMsg = "No instance for (GHC.Num.Num GHC.Base.String)\n
arising from a use of `GHC.Num.+'\nPossible fix:\n  add an instance
declaration for (GHC.Num.Num GHC.Base.String)"}

There is no context (line number, code snippets...), plus the error message
uses fully qualified names, which is not very readable.
It's very hard to figure out where the problem is when interpreting a long
string.
But the same error in a file that is loaded with Hint gives the correct
message (uncomment the putStrLn in SomeModule.hs to get it):

GhcError {errMsg = ":\n[1 of 1] Compiling
SomeModule   ( SomeModule.hs, interpreted )"},GhcError {errMsg =
"SomeModule.hs:5:22:\nNo instance for (Num String) arising from a use
of `+'\nPossible fix: add an instance declaration for (Num String)\n
In the second argument of `($)', namely `\"bar\" + 1'\nIn a stmt of a
'do' block: putStrLn $ \"bar\" + 1\nIn the expression:\n  do {
putStrLn \"bar\";\n   putStrLn $ \"bar\" + 1 }"}

This error is much better: it gives line number plus some code snippets
("In the second argument of...").

There might be a flag that is not correctly set in GHC? After a quick look
I'm thinking of GHC.DynFlags (I'm no expert). Now it is configured with:
configureDynFlags :: GHC.DynFlags -> GHC.DynFlags
configureDynFlags dflags = dflags{GHC.ghcMode= GHC.CompManager,
  GHC.hscTarget  = GHC.HscInterpreted,
  GHC.ghcLink= GHC.LinkInMemory,
  GHC.verbosity  = 0}

Thanks,
Corentin
import Control.Monad
import Language.Haskell.Interpreter

main :: IO ()
main = do r <- runInterpreter testHint
  case r of
Left err -> printInterpreterError err
Right () -> putStrLn "that's all folks"

testHint :: Interpreter ()
testHint =
do
  loadModules ["SomeModule.hs"]
  setTopLevelModules ["SomeModule"]
  setImportsQ [("Prelude", Nothing)]
  --the following expression will generate an error message without context??
  let expr = "do\n   putStrLn \"foo\"\n   putStrLn $ \"bar\" + 1\n"
  interpret expr (as :: IO ())
  return ()

printInterpreterError :: InterpreterError -> IO ()
printInterpreterError e = putStrLn $ "Ups... " ++ (show e)

module SomeModule where

f = do
   putStrLn "foo"
   -- uncomment to see error message with module loading 
   --putStrLn $ "toto" + 1 
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs