mitchell vitez blog music art games dark mode

Misadventures in GHC API Windows DLLs

I was recently messing around with writing a program that could “check” some Haskell code, and give the user some feedback. For example, it could give you a small task to do like this:

-- Define a function body that adds 1 to an Int
f :: Int -> Int

Then the user could respond with this input, and the checker would verify the program automatically.

f = (+1)

However, I also wanted this checker to work on Windows, and from the context of an already-running C++ program. This is the part that ballooned into hours of struggle.

Fair warning: I have barely any idea what I’m talking about for long stretches here. These are misadventures for a reason! If there’s something I missed that would have ended my troubles, please feel free to reach out.

What the checker checks

The checker checks that a user-supplied piece of code:

Sample runs

Here are some sample inputs and outputs demonstrating failure of each of the above checks. I’ll list the failure type, the user’s input, and the program’s output in response.

Setting up a GHC session

The way the checker works is by setting up a GHC interpreter session, and running the user-provided code in that context.

Below, we set flags on the GHC session to interpret (rather than compile) and also to LinkInMemory. Keep that linking method in mind—it’ll come up later.

The index argument is provided so we can run multiple GHC sessions at the same time. We can write multiple modules (Temp0, Temp1, Temp2, etc.) and spin up a separate GHC session to check each one. This lets us do things like run tests concurrently—at least on Mac (more on that later too).

setupGhcSession :: String -> Int -> Ghc ()
setupGhcSession userCode index = do
  dynFlags <- getSessionDynFlags
  let
    newDynFlags = dynFlags
      { backend = interpreterBackend
      , ghcLink = LinkInMemory
      }
  void $ setSessionDynFlags newDynFlags

We take the user’s code and write it to a file as part of a larger module, most of which we control.

  let moduleName = tempModulePrefix <> show index
      code =
        "module " <> moduleName <> " where\n" <>
        "f :: Int -> Int\n" <>
        userCode
  liftIO $ writeFile (moduleName <> ".hs") code

Finally, we need to tell GHC which targets to load. In this case, the only target will be the module we just made.

  target <- guessTarget (moduleName <> ".hs") Nothing Nothing
  setTargets [target]
  void $ load LoadAllTargets

Running each checker stage

The bulk of the program is in a function called check. It takes the user’s code and runs multiple stages of checkers on it, returning early if anything goes wrong along the way. Here’s a simplified skeleton:

check :: String -> IO (Int, String)
check userCode = runGhc (Just libdir) $ do
  setupGhcSession userCode 0
  -- parse
  -- typecheck
  -- test
  -- check style

Foreshadowing some FFI (foreign function interface) concerns, we see that check returns (Int, String). This is because it’s giving back a return code as well as a message. For COMPILER_ERRORs, this message is just GHC’s error message piped along, but it could be a custom message in the case of a STYLE_WARNING or TEST_FAILURE. Because the FFI doesn’t support passing an enum across the boundary (at least that I know of…), we return a number which has a specific meaning by convention:

retcode_COMPILER_ERROR = 3
retcode_TEST_FAILURE   = 2
retcode_STYLE_WARNING  = 1
retcode_ALL_GOOD       = 0

Parsing stage

The first stage of check is parsing. We attempt to parse the module using the GHC-API-provided parseModule function. This function throws an exception if parsing fails, so we have to try it. We use Control.Monad.Catch.try rather than Control.Exception.try because its type is (HasCallStack, MonadCatch m, Exception e) => m a -> m (Either e a) not Exception e => IO a -> IO (Either e a), and we’re operating in the Ghc monad, not IO.

  parsedModuleE <- Control.Monad.Catch.try $ parseModule modSummary
  case parsedModuleE of
    Left (err :: SourceError) -> liftIO $
      pure (retcode_COMPILER_ERROR, cleanupErrMsg err)
    Right parsedModule -> do
      -- keep going

Typechecking stage

The typechecking stage is extremely similar to the parsing stage.

  typecheckedModuleE <- Control.Monad.Catch.try $ typecheckModule parsedModule
  case typecheckedModuleE of
    Left (err :: SourceError) -> liftIO $
      pure (retcode_COMPILER_ERROR, cleanupErrMsg err)
    Right _typecheckedModule -> do
      -- keep going

Testing stage

The testing stage is the most intricate, because it does a lot more than call a GHC-provided function and case on its result.

Let’s say below are the tests we want to run. We check the result of running some string of Haskell code (e.g. f 2) in an environment containing the user-provided code (a definition of f). Our test runner will be using Dynamic, so we apply the type of the result we want to see as well.

  let
    tests =
      [ test @Int 3 "f 2"
      , test @Int 0 "f (-1)"
      , test @Int 1000 "f 999"
      ]

The test runner will runTest on each test in parallel, and if they don’t all pass it collects the results and reports back to the user.

  results <- liftIO . mapConcurrently (runTest userCode) $ zip [1..] tests
  if not $ all testPassed results
  then liftIO $ do
    let resultsStr = intercalate "\n" [s | TestResult (Just s) <- results]
    pure (retcode_TEST_FAILURE, resultsStr)
  else
    -- keep going

This makes runTest a pretty important bit of internal machinery. Ghc doesn’t have the ability to share information across sessions (again, as far as I could tell). So, runTest takes the user-provided code, spins up a new GHC session per test, and uses the Int as an index into which test it’s working on. Most of that complexity exists to support concurrent testing.

runTest :: String -> (Int, Ghc TestResult) -> IO TestResult
runTest userCode (index, testAction) = runGhc (Just libdir) $ do
  setupGhcSession userCode index
  setContext [IIModule $ mkModuleName $ tempModulePrefix <> show index]
  testAction

The actual test function then compiles each test String as an actual Haskell expression with dynCompileExpr, in the context of the user-supplied code. It’s careful to catch any exceptions and to include a timeout in case the user provides code which infinitely loops.

test :: forall a. (Eq a, Show a, Typeable a) => a -> String -> Ghc TestResult
test expected code = do
  actualDyn <- dynCompileExpr code
  liftIO $ case fromDynamic actualDyn of
    Nothing -> pure . TestResult $ Just "Somehow, that's the wrong type"
    Just actual -> do
      let name = code <> " == " <> show expected
          oneSecond = 10^(6 :: Int)
      resultE <- try . timeout oneSecond $ testMsg name actual expected
      case resultE of
        Right Nothing -> do
          pure . TestResult . Just $ "❌ " <> name <> " failed: timed out. maybe an infinite loop?"
        (Left (_ :: SomeException)) -> do
          pure . TestResult . Just $ "❌ " <> name <> " failed: threw an exception"
        Right (Just res) -> pure res

Style check stage

Finally, we get a chance to treat the user’s code as a plain old String. We can check for any style inconsistencies, make recommendations, and so on. Here’s a simplified example that checks whether the user’s code is an exact match of our expected final answer.

  if userCode /= "f = (+1)"
  then do
    let
      suggestion = unlines
        [ "You wrote"
        , userCode
        , "Consider using an operator section, e.g."
        , "g = (*2)"
        ]
    pure (retcode_STYLE_WARNING, suggestion)
  -- keep going

Finally, if everything looks good, we feed that information back.

  else pure (retcode_PASS, "")

C++ FFI

So far, so good. However, I also wanted to run my Haskell program from an existing C++ program. I’ve used Haskell’s foreign function interface before, so this didn’t seem too ominous. First, we need a language extension.

{-# LANGUAGE ForeignFunctionInterface #-}

Because our code will be called by C++, we do a foreign export. We continue taking in the user’s code as input, but now it’s a CString rather than a Haskell String. Also, instead of returning (Int, String), we return just the CInt return code. For the return message, we’ll pass it back by updating a Ptr CString to point to the new message that Haskell provides.

foreign export ccall check :: CString -> Ptr CString -> IO CInt

Since it’s read-only, we can easily get back our old userCode binding by converting from CString to String.

check :: CString -> Ptr CString -> IO CInt
check userCodeCStr retmsg = do
  userCode <- peekCString userCodeCStr

However, the difference in return types does affect some downstream code. Instead of packaging our two return values into a tuple:

  pure (retcode_COMPILER_ERROR, cleanupErrMsg err)

We return only the retcode. The retmsg is set by updating check’s Ptr CString argument so that it points at a new Haskell-defined CString.

  withCString (cleanupErrMsg err) $ \cStr -> poke retmsg cStr
    pure retcode_COMPILER_ERROR

On the C++ side, we’ll need to say that check exists and is coming from elsewhere. We also have to let our program know about hs_init and hs_exit. Haskell ships with a “runtime system” (RTS). The RTS is linked with each Haskell program, and is required for a Haskell program to run. So, we have to tell C++ that we want to spin up the Haskell RTS at the time we run our Haskell program from C++.

extern "C" {
  int check(const char* userCode, char** retmsg);
  void hs_init(int *argc, char ***argv);
  void hs_exit();
}

The first thing we do in our C++ program’s main is call hs_init.

int main() {
  hs_init(NULL, NULL);

Then, we can read in user input to an input variable and set up a retmsg_cstr pointer, which will correspond to the retmsg returned by Haskell.

  std::cout << "\n-- Define a function body that adds 1 to an Int\nf :: Int -> Int" << std::endl;
  std::string input;
  std::getline(std::cin, input);

  char* retmsg_cstr;

Our call to Haskell’s check function looks like:

  int retval = check(input.c_str(), &retmsg_cstr);

Once Haskell returns back to us, we immediately copy retmsg into a std::string, to make sharing a pointer across the boundary a little less worrisome.

  std::string retmsg = std::string(retmsg_cstr);

We can use the retval and retmsg to print out a nicely-formatted colorful message to the end user.

  switch (retval) {
    case 3: printf("\033[31mCOMPILATION ERROR\033[0m\n"); break;
    case 2: printf("\033[38;5;214mTEST FAILURE\033[0m\n"); break;
    case 1: printf("\033[93mSTYLE WARNING\033[0m\n"); break;
    case 0: printf("\033[32mALL GOOD\033[0m\n"); break;
  }
  std::cout << retmsg << std::endl;

If the user-supplied program wasn’t correct, we have them try again with a different input.

  if (retval != 0) { main(); }

Finally, we shut down the Haskell RTS and finish up.

  hs_exit();
  return 0;
}

Building on Mac

While the bulk of my hours (and suffering) were spent on Windows, building this whole contraption on Mac wasn’t trivial either. We are trying to juggle two complex compilers and make them play nice….

At first, I was including HsFFI.h…or at least, attempting to.

Check.cpp:3:10: fatal error: 'HsFFI.h' file not found
3 | #include <HsFFI.h>
  | ^~~~~~~~~

However, I didn’t really know what it was for. Turns out, we only need the two runtime hooks we introduced before—hs_init and hs_exit. So, declaring these in the extern "C" block turned out to be much easier than figuring out how to link against HsFFI.h.

Then, I started running into this familiar-seeming linker error. It’s a real classic.

Undefined symbols for architecture arm64:
  "_check", referenced from:
    _main in Check-f0137d.o
  "_hs_exit", referenced from:
    _main in Check-f0137d.o
  "_hs_init", referenced from:
    _main in Check-f0137d.o
ld: symbol(s) not found for architecture arm64

Of course, this just meant that I wasn’t actually linking together the programs correctly.

I didn’t want to force my final “end users” (current status: imaginary) to install GHC on their systems. This means we have to bake the Haskell RTS into our program somehow. My first attempts were pretty confused:

ghc -shared -dynamic -fPIC Check.hs \
  -o libcheck.dylib -no-hs-main
g++ -std=c++17 Check.cpp

Banging my head against this wall was not a particularly fruitful strategy. I still have no clue what this line was trying to tell me:

ld: invalid use of ADRP/imm12 in '' to '_stg_bh_upd_frame_info'

Eventually, some partial progress happened. check was a defined symbol! Now, I “only” had to link in the RTS.

Undefined symbols for architecture arm64:
  "_hs_exit", referenced from:
    _main in Check-1b5aaf.o
  "_hs_init", referenced from:
    _main in Check-1b5aaf.o
ld: symbol(s) not found for architecture arm64

The eventual realization spawned here was that on Mac I should statically link in the RTS rather than going through a dylib. After adding the -staticlib flag, I got something new: an even bigger, more confusing error message! (Truncated for brevity.)

Undefined symbols for architecture arm64:
  "_ffi_call", referenced from:
    _interpretBCO in libcheck.a[2276](Interpreter.thr_o)
    _interpretBCO in libcheck.a[2276](Interpreter.thr_o)
    _rtsSyms in libcheck.a[2304](RtsSymbols.thr_o)
  "_ffi_closure_alloc", referenced from:
    _createAdjustor in libcheck.a[2380](LibffiAdjustor.thr_o)
  "_ffi_closure_free", referenced from:
    _freeHaskellFunctionPtr in libcheck.a[2380](LibffiAdjustor.thr_o)
  "_ffi_prep_cif", referenced from:
  ...

The fix to that turned out to be to link against libffi, which I could do with:

  -L/opt/homebrew/opt/libffi/lib -lffi

After doing that, a somewhat-similar error cropped up:

Undefined symbols for architecture arm64:
  "_iconv", referenced from:
    _hs_iconv in libcheck.a[1464](iconv.o)
  "_iconv_close", referenced from:
    _hs_iconv_close in libcheck.a[1464](iconv.o)
  "_iconv_open", referenced from:
    _hs_iconv_open in libcheck.a[1464](iconv.o)
  "_locale_charset", referenced from:
    _localeEncoding in libcheck.a[1462](PrelIOUtils.o)
ld: symbol(s) not found for architecture arm64

Luckily, I had just dealt with a bunch of "_ffi errors fixed by linking in libffi, so linking in iconv was a pretty natural solution.

  -liconv -framework CoreFoundation

All told, the final Mac build.sh script looks like this:

ghc -O2 -staticlib -fPIC -threaded -no-hs-main \
  Check.hs \
  -o libcheck.a
g++ -std=c++17 Check.cpp \
  libcheck.a \
  -L/opt/homebrew/opt/libffi/lib -lffi \
  -liconv -framework CoreFoundation \
  -o run_check
./run_check

Revenge of the Diff

After all that, I was able to build the program on Mac. It started acting up though, when I tried to parallelize the tests with mapConcurrently:

<unknown>: Temp.hs: withFile: resource busy (file is locked)

This wasn’t hard to diagnose or fix. The resource contention for files meant we needed to use separate files. This directly led to the index numbering scheme above, where each separate GHC session is working on a separate module, all at the same time.

However, this easy change then led to my first ultra-confusing bug. I would provide input like f = x +, which should definitely be a compilation error—it shouldn’t parse. However, the program was reporting that this was a STYLE WARNING instead, seemingly skipping over the parsing step to a later stage. f = "hello" (with its definite typechecking problem) was also reportedly a style issue.

This behavior was absolutely bewildering.

After much consternation, eventually the bug was rooted out. By checking parseModule directly I noted that it definitely wasn’t returning Left or throwing an exception when encountering bad code. However, I was passing it the right arguments—they hadn’t changed from before.

Turns out parseModule is dependent on the context of its Ghc monad surroundings, based on which target you set. I had a setup like:

  let moduleName = "Temp"
  target <- guessTarget (moduleName <> ".hs") Nothing Nothing
  setTargets [target]

This would set Temp.hs as a target, but not Temp1.hs or Temp2.hs etc. So my code would run up to the point of the concurrent tests, and then each test would skip parsing and typechecking because there wasn’t a relevant target hanging around.

I had been duped by parseModule taking a ModSummary argument—I figured that argument was the relevant module to parse. However, once noting the target actually came from surrounding context, the fix was relatively simple:

  let moduleName = "Temp" <> show index

After that, concurrent tests ran great.

Building on Windows

At this point, I had the bright idea to make my checker program work cross-platform on Windows. How hard could it be? However, I wasn’t super well set-up to build Haskell programs on Windows. In fact, I didn’t even have ghc installed on my PC:

'ghc' is not recognized as an internal or external command, operable program or batch file.

Just like that, we’re off to the spend-your-whole-weekend-debugging races.

I installed GHC via direct download of the Windows version. I also didn’t have a C++ compiler (like cl or g++). While I would eventually end up installing g++, I started by downloading cl via the Visual Studio Build Tools. Keep in mind that I still naively thought I was a few missing installs away from cross-platform support.

After getting some compilers downloaded, “could not load module GHC” was the first real error. This error means that GHC can’t find its own library files. I helped GHC out by telling it where it lives via the PATH environment variable.

Next up, a very familiar error to a seasoned Haskeller:

Could not find module `Control.Concurrent.Async'.

This means that I need to cabal install --lib async. First, though, I had to install cabal.

'cabal' is not recognized as an internal or external command, operable program or batch file.

After this third installation prompt, I figured since my Mac already had all the required tools installed, maybe I’d give cross-compilation a shot.

brew install mingw-w64

Cross-compilation means building a program intended for one system on another system. In this case, I was building a Windows DLL on my Mac. The initial errors didn’t seem too bad, since I had already dealt with linker issues during the Mac build process before.

x86_64-w64-mingw32-g++ -shared -o check.dll Check.cpp libcheck.a \
    -static-libgcc -static-libstdc++ -lpthread

    /opt/homebrew/Cellar/mingw-w64/13.0.0_2/toolchain-x86_64/bin/x86_64-w64-mingw32-ld: /var/folders/x7/g9_jxglx7s1c51gztr49n2800000gn/T//ccQCjQan.o:Check.cpp:(.text+0x21): undefined reference to `hs_init'
    /opt/homebrew/Cellar/mingw-w64/13.0.0_2/toolchain-x86_64/bin/x86_64-w64-mingw32-ld: /var/folders/x7/g9_jxglx7s1c51gztr49n2800000gn/T//ccQCjQan.o:Check.cpp:(.text+0x83): undefined reference to `check'
    /opt/homebrew/Cellar/mingw-w64/13.0.0_2/toolchain-x86_64/bin/x86_64-w64-mingw32-ld: /var/folders/x7/g9_jxglx7s1c51gztr49n2800000gn/T//ccQCjQan.o:Check.cpp:(.text+0x152): undefined reference to `hs_exit'
    collect2: error: ld returned 1 exit status`

However, because Haskell programs need to ship with an RTS, this meant I would need to build a Windows RTS DLL on my Mac, as well as building my own program. That didn’t sound all that fun, so I switched back over to the Windows computer in a hurry.

With renewed resolve, I dedicated myself to the project of getting this thing building entirely on a Windows machine.

Missing symbols

While I’ve taken a few liberties above, here is where the story starts to become egregiously chronologically jumbled. I was debugging all of the following issues at once, jumping to whatever front of the war currently seemed most promising. This was mixed in with taking walks to clear my head, and starting another playthrough of Sekiro. I’d rather face the Chained Ogre a hundred times than stare down another DLL with missing symbols.

Instead of chronological order, I’ll organize into sections categorized by which error I was dealing with. In this section, we’ll talk about missing symbols, a problem which in real life spanned several hours over multiple days.

I was using ghc to produce a check.dll.

ghc -O2 -shared -no-hs-main Check.hs -o check.dll

By now I had installed mingw tools including g++ and nm. We can use nm to find whether a symbol exists in a DLL.

"C:\Program Files\mingw\bin\nm.exe" check.dll | findstr check

This found several symbols containing the word check, but none of them were my actual check function. We can search for just check with nothing after it by adding a dollar sign.

"C:\Program Files\mingw\bin\nm.exe" check.dll | findstr "check$"

This was empty. I had no idea why, and wasn’t even sure whether that was a problem. There’s another way to find these symbols:

dumpbin /EXPORTS check.dll | findstr "check$"

Eventually, on some website or other, I found that Windows DLLs have an exported symbol limit of 65536. Including every symbol from the Haskell RTS was putting me over that cap, and simply silently omitted other symbols like my check I wanted to find.

The solution is to provide another argument to ghc, with the name of a .def file.

ghc -O2 -shared -no-hs-main Check.hs -o check.dll exports.def

The contents of exports.def are:

EXPORTS
  check
  hs_init
  hs_exit

Instead of exporting over 65536 symbols, I was now exporting three. A quick test confirms that the check symbol can now be found.

dumpbin /EXPORTS check.dll | findstr "check$"
          1    0 000B1830 check

"C:\Program Files\mingw\bin\nm.exe" check.dll | findstr "check$"
00000001800b1830 T check

Missing packages

When I did cabal install async, ghc-pkg list wasn’t showing it as installed. Sometimes I forget the --lib flag (as in cabal install --lib async), but that didn’t work either.

Cabal was installing libraries for a different version of ghc than the one I was using (9.10.3). This was probably because I had installed cabal and ghc as two separate downloads. I switched to having ghcup manage both, and deleted both other (yes, there were multiple) bad versions of ghc from my system.

ghcup install ghc 9.10.3
ghcup set ghc 9.10.3

I continued getting a cannot satisfy -package-id base-4.20.2.0-39f9 error until I cleaned out my cabal packages and reinstalled new versions.

Linking libraries

When g++ tries to link a DLL it can’t find, Windows throws up a System Error dialog (not a response in the command prompt).

The code execution cannot proceed because libstdc++-6.dll was not found. Reinstalling the program may fix this problem.

The fix isn’t too bad. We need to add -static-libstdc++ to our g++ invocation.

The code execution cannot proceed because libgcc_s_seh-1.dll was not found. Reinstalling the program may fix this problem.

Another missing DLL. Similarly, we add -static-libgcc.

The code execution cannot proceed because libwinpthread-1.dll was not found. Reinstalling the program may fix this problem.

You might suspect a similar answer as above. However, -static-lpthread doesn’t exist.

g++.exe: error: unrecognized command-line option '-static-lpthread'

When you provide -lpthread you get the same error as not providing it at all.

The code execution cannot proceed because libwinpthread-1.dll was not found. Reinstalling the program may fix this problem.

Instead, you have to provide -static -lpthread. Not sure why.

This makes our final g++ invocation:

"C:\Program Files\mingw\bin\g++.exe" -std=c++17 \
  Check.cpp check.lib \
  -static-libgcc -static-libstdc++ -static-lpthread \
  -o run_check.exe

The overall build.bat file ended up being:

ghc -O2 -shared -no-hs-main Check.hs -o check.dll exports.def
"C:\Program Files\mingw\bin\dlltool.exe" -D check.dll -d exports.def -l check.lib
"C:\Program Files\mingw\bin\g++.exe" -std=c++17 Check.cpp check.lib -static-libgcc -static-libstdc++ -static -lpthread -o run_check.exe
run_check.exe

m32_alloc_page

Finally, we arrive at m32_alloc_page, my new friend.

Our linking strategy is something we can set when creating a GHC session. DynFlags has a GhcLink field. According to the documentation, the options include:

I had picked LinkInMemory. This tragic misstep led to an error message that contained a dump with a whole bunch (at least hundreds) of memory locations and their contents, followed by:

run_check.exe: internal error: m32_alloc_page: failed to allocate pages within 4GB of program text (got 00007ff62f480000)
    (GHC version 9.10.3 for x86_64_unknown_mingw32)
    Please report this as a GHC bug:  https://www.haskell.org/ghc/reportabug

When I see “GHC bug” pop up on my screen, I like to try to find the relevant code. The definition of m32_alloc_page was pretty quick to search for.

static struct m32_page_t *
m32_alloc_page(void)

And look, down here is the error message! It’s preceded by reportMemoryMap() which was presumably the source of the giant error output.

  barf("m32_alloc_page: failed to allocate pages within 4GB of program text (got %p)", chunk);

GHC is barfing chunks. Lovely.

Switching to the LinkBinary linking strategy seemed to clear up this problem for the main GHC session. However, remember that I was running multiple other sessions to run tests concurrently.

I did some good old-fashioned print debugging to narrow down the source of the error. It was happening in dynCompileExpr inside the testing stage. This meant that if some user code failed to parse or typecheck, the overall output would actually be correct, but if it was good enough to undergo testing you’d get the giant m32_alloc_page error dump.

  liftIO $ putStrLn "before dynCompileExpr"
  actualDyn <- dynCompileExpr code
  liftIO $ putStrLn "after dynCompileExpr"

It seemed like no matter what I did, dynCompileExpr would lead to an m32_alloc_page error cropping up. Setting the DynFlags somehow didn’t seem to affect it.

dynCompileExpr calls compileParsedExpr which calls compileParsedExprRemote which contains this line:

  let dflags = hsc_dflags hsc_env

hsc_env comes from withSession which calls getSession which comes from the GhcMonad definition:

class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger m ) => GhcMonad m where
  getSession :: m HscEnv
  setSession :: HscEnv -> m ()

However, even updating the session right before dynCompileExpr seemed to have no effect:

  sess <- getSession
  let sess' = sess { hsc_dflags = (hsc_dflags sess) { ghcLink = LinkBinary } }
  void $ setSession sess'
  actualDyn <- dynCompileExpr code

Of course, some linking methods won’t work at all:

Cannot add module Temp1 to context: not interpreted

It makes sense that the interpreter only supports certain linking methods, like LinkInMemory. However, I’m still not sure why LinkBinary works for the first session but not for later ones, while LinkInMemory doesn’t work at all.

Standalone exe

At wit’s end, I decided to take a different approach. We can build a standalone Windows executable, and call it as a subprocess from C++.

This means we need to introduce a main function and remove the foreign export.

main :: IO ()
main = do
  (userCode:_) <- getArgs
  result <- check userCode
  print $ fst result
  putStrLn $ snd result

check :: String -> IO (Int, String)
check userCode = do
  ...

This can be built with -optl-static

ghc -O2 -threaded -static -optl-static Main.hs -o main.exe

and run with the user’s program as an argument.

main.exe "f = (2*)"

Closing thoughts

It would be really great to figure out how to get these GHC API sessions working on Windows as well as they do on Mac, so if you have tips let me know. I’d especially like a workaround for the m32_alloc_page error that doesn’t “give up on the idea” as much as the subprocess solution does.

In some sense, we’re trying to execute arbitrary Haskell programs without installing GHC. It makes sense this might be a bit tricky.

So what did we learn here, anyway?

In summary, I think the moral of the story is:

If at first you don’t succeed, try, try again, and you might end up with something vaguely resembling what you originally wanted

Isn’t that beautiful?