Debug GHC compilation error returned at runtime by hint's `Language.Haskell.Interpreter.runInterpreter`

倾然丶 夕夏残阳落幕 提交于 2020-01-05 04:11:07

问题


I've re-posted this question to focus more tightly on the specific error, and to better enumerate what I've already tried.

I'm trying to parse some Haskell code during the runtime of a Haskell program using the hint package.

The outer program compiles, but when I run it the inner compilation step fails. I'm getting a description of what I assume is a syntax problem, and a location in the "interactive" code, but I have no idea how to view the code in question.

Here's Main.hs

module Main where

import Data.List (intercalate)
import Polysemy (runM)
import qualified Language.Haskell.Interpreter as H

import qualified Effects as E

handleFailures :: Either H.InterpreterError a -> IO a
handleFailures (Left l) = ioError $ userError $ message l
  where
    message (H.WontCompile es) = intercalate "\n" (header : map unbox es)
    message e = show e
    header = "ERROR: Won't compile:"
    unbox (H.GhcError e) = e
handleFailures (Right a) = return a

interpretation :: String -> H.Interpreter E.MyEffect
interpretation s = do
  H.loadModules ["Effects"]
  H.setImportsQ [("Prelude", Nothing), ("Effects", Nothing)]
  effect <- H.interpret s (H.as :: E.MyEffect)
  return effect

extractProgram :: String -> IO E.MyEffect
extractProgram s = do
  p <- H.runInterpreter $ interpretation s
  success <- handleFailures p
  return success

main :: IO ()
main = do
  userProvided <- readFile "UserProvided.hs"
  userProgram <- extractProgram userProvided
  runM . E.teletypeToIO . E.teletypePlusToIO $ userProgram

Effects.hs defines and provides helpers for a Polysemey Sem monad called MyEffect.

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE LambdaCase, BlockArguments #-}
{-# LANGUAGE GADTs, FlexibleContexts, TypeOperators, DataKinds, PolyKinds, ScopedTypeVariables #-}

module Effects where

import Polysemy

data Teletype m a where
  ReadTTY  :: Teletype m String
  WriteTTY :: String -> Teletype m ()

makeSem ''Teletype

teletypeToIO :: Member (Embed IO) r => Sem (Teletype ': r) a -> Sem r a
teletypeToIO = interpret $ \case
  ReadTTY      -> embed getLine
  WriteTTY msg -> embed $ putStrLn msg

data TeletypePlus m a where
  ReadPlus  :: TeletypePlus m String
  WritePlus :: String -> TeletypePlus m ()

makeSem ''TeletypePlus

teletypePlusToIO :: Member (Embed IO) r => Sem (TeletypePlus ': r) a -> Sem r a
teletypePlusToIO = interpret $ \case
  ReadPlus      -> embed $ ("+" <>) <$> getLine
  WritePlus msg -> embed $ putStrLn $ msg <> "+"

type MyEffect = Sem [TeletypePlus, Teletype, Embed IO] ()

UserProvided.hs contains a simple do expression in MyEffect.

do
  i <- readTTY
  j <- readPlus
  let k = i <> j
  writeTTY k
  writePlus k 

In order to get the polysemy package available at runtime, I have to enter run it from inside a cabal sandbox.

$ cabal build
    Build profile: -w ghc-8.8.1 -O1
    In order, the following will be built (use -v for more details):
     - Hello-Polysemy-0.1.0.0 (exe:Hello-Polysemy) (file Main.hs changed)
    Preprocessing executable 'Hello-Polysemy' for Hello-Polysemy-0.1.0.0..
    Building executable 'Hello-Polysemy' for Hello-Polysemy-0.1.0.0..
    [2 of 2] Compiling Main             ( Main.hs, /home/mako/Git/Hello-Polysemy/dist-newstyle/buil/x86_64-linux/ghc-8.8.1/Hello-Polysemy-0.1.0.0/x/Hello-Polysemy/build/Hello-Polysemy/Hello-Polysemy-tmp/Main.o )
    Linking /home/mako/Git/Hello-Polysemy/dist-newstyle/build/x86_64-linux/ghc-8.8.1/Hello-Polysemy-0.1.0.0/x/Hello-Polysemy/build/Hello-Polysemy/Hello-Polysemy ...
$ cabal exec bash

... but then ...

$ cabal run
    Up to date
    Hello-Polysemy: user error (ERROR: Won't compile:
    <interactive>:10:135: error:
        Operator applied to too few arguments: :)

So far as I can tell the only place I'm using the : operator is in Effects.hs, where (a) I'm actually using the type-operator ':, and (b) compilation succeeds just fine when Effects is imported into Main.hs.

Any suggestions for what the problem might be, or how I could learn more?

I already tried using Language.Haskell.Interpreter.Unsafe.unsafeRunInterpreterWithArgs ["-v4"]. That clarifies that it's talking about ghc-prim:GHC.Types.:{(w) d 66}), but I don't know what to do with that information.

Update:

I've tried various permutations of in-lining the "userProvided" code.
declaring the exact same Effect value inline in Main works fine. Replacing the string read from the file with an inline string of an even simpler value "writePlus \"asdf\"" doesn't change the error message.

来源:https://stackoverflow.com/questions/59446654/debug-ghc-compilation-error-returned-at-runtime-by-hints-language-haskell-inte

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!