[Haskell-cafe] plugins and internal error: stg_ap_v_ret
Michael Snoyman
michael at snoyman.com
Mon Jan 31 20:11:10 CET 2011
Hi all,
I'm trying to convert wai-handler-devel to use plugins instead of
hint, but cannot even get some basic usages to work properly. I've put
together a minimal example that loads a WAI application from a
separate file and runs it, but this immediately causes the program to
crash saying:
loader: internal error: stg_ap_v_ret
(GHC version 6.12.3 for i386_unknown_linux)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Is this an actual bug in GHC, or am I misusing the plugins package?
The two source files:
MyModule.hs
{-# LANGUAGE OverloadedStrings #-}
module MyModule where
import Network.Wai
import Data.ByteString.Lazy.Char8 ()
myapp _ = responseLBS status200 [("Content-Type", "text/plain")] "myapp"
loader.hs
import System.Plugins.Make
import System.Plugins.Load
import Network.Wai.Handler.Warp (run)
main :: IO ()
main = do
MakeSuccess _ obj <- makeAll "MyModule.hs" []
LoadSuccess _ app <- load_ obj [] "myapp"
run 3000 app
Thanks,
Michael
More information about the Haskell-Cafe
mailing list