Hint.interpret 在 Polysemy.Sem 值上使用时会出现编译器错误

Sha*_*ter 7 haskell runtime hint ghc haskell-polysemy

我正在尝试使用 Hint ( Language.Haskell.Interpreter )在运行时编译Polysemy monad 值 )。

当我尝试这样做时,我确实得到了一个关于:在“交互式”代码中不正确使用运算符的错误;似乎传递给 GHC 的文本提示存在语法错误。

{-# LANGUAGE DataKinds #-}

module Main where

import Polysemy (Embed, embed, runM, Sem)
import Language.Haskell.Interpreter (as, interpret, Interpreter, runInterpreter, setImportsQ)
import Data.Typeable (typeOf)
import Control.Monad.IO.Class (liftIO)

main :: IO ()
main = do
  -- Hint works fine to interpret a String:
  m <- interpretWithErrors exampleHint
  print m
  -- And Sem works fine:
  runM exampleSem
  -- But notice the weird detected type:
  print $ typeOf exampleSem
  -- And now Hint fails to interpret a Sem:
  s <- interpretWithErrors exampleBoth
  print $ typeOf s
  runM s

type MyEffect = Sem '[Embed IO] ()

exampleSem :: MyEffect
exampleSem = embed $ print "Successful Sem!"

exampleHint :: Interpreter String
exampleHint = do
  setImportsQ [("Prelude", Nothing)]
  interpret "\"Successful Hint!\"" (as :: String)

exampleBoth :: Interpreter MyEffect
exampleBoth = do
  setImportsQ [("Prelude", Nothing), ("Polysemy", Nothing)]
  liftIO $ print "Successfully imported!"
  -- This is where it fails:
  s <- interpret "embed $ print \"Success!\"" (as :: MyEffect)
  liftIO $ print "Successfully interpreted!"
  return s

interpretWithErrors :: Interpreter a -> IO a
interpretWithErrors i_a = do
  e_e_a <- runInterpreter i_a
  either (ioError . userError . show) (return) e_e_a
Run Code Online (Sandbox Code Playgroud)

运行上面的打印:

"Successful Hint!"
"Successful Sem!"
Sem (': ((* -> *) -> * -> *) (Embed IO) ('[] ((* -> *) -> * -> *))) ()
"Successfully imported!"
Hint-Polysemy: user error (WontCompile [GhcError {errMsg = "<interactive>:3:41: error: Operator applied to too few arguments: :"}])
Run Code Online (Sandbox Code Playgroud)

一些注意事项:

  • 我正在使用 cabal,并且为了通过 import在解释器 monad 中行,我必须从 cabal 沙盒外壳中运行它,因为 Polysemy 并未安装到我的机器上。
  • 也就是说,我不认为阴谋集团或进口 Polysemy 是问题所在。如果我只是忽略导入 Polysemy,我会得到与上面完全相同的错误消息setImportsQ [("Prelude", Nothing)].
  • 我正在解释的字符串甚至不需要是一个有效的表达式;我可以在不改变错误的情况下把胡言乱语放在那里。这向我表明问题出在(as :: MyEffect).
  • 我包括typeOf来证明这MyEffect实际上是Typeable
  • 我不知道为什么typeOf exampleSem要给出这么长而奇怪的类型签名。我确实认为这就是问题所在。重新排列MyEffecttype MyEffect = Sem ((Embed IO) : []) ()没有效果。

如果我做错了什么,有人清楚吗?我应该如何尝试调试这个问题?
假设这是Type.Reflection.Typeable中的提示、多义或(不太可能)中的错误,我的下一步是尝试修复它吗?我想我必须以某种方式确定哪个库有问题?

这是对先前问题的改进。这是原文。

luq*_*qui 4

不是答案,但我发现了一些可能对您有用的发现。

我认为这可能是虚假的前缀类型运算符语法': x xs,它不是有效的 Haskell(你必须将其写为 infix 或使用(':))。所以我实现了一个SemWorkaround包装模块,它使用ConsandNil代替标准列表语法。看起来几乎是同样的问题,但有更详细的错误消息(嗯)。

然后我认为这可能是显式类型的应用程序,因为错误消息一直在谈论给予太多参数的事情。因此,我尝试将类型级列表表示更改为我们过去使用的方式。

{-# LANGUAGE DataKinds, TypeOperators, TypeFamilies #-}

module SemWorkaround where

import Polysemy (Sem, Embed)
import Data.Kind (Type)

data Nil 
data Cons (a :: (Type -> Type) -> Type -> Type) (as :: Type)

type family ListToList xs where
    ListToList Nil = '[]
    ListToList (Cons x xs) = x ': ListToList xs

newtype Sem' l a = Sem' { getSem' :: Sem (ListToList l) a }
Run Code Online (Sandbox Code Playgroud)

并用于Sem'封送提示边界。例如

type MyEffect' = Sem' (Cons (Embed IO) Nil) ()

...

s <- interpret "Sem' . embed $ print \"Success\"" (as :: MyEffect')
pure $ getSem' s
Run Code Online (Sandbox Code Playgroud)

这有效。因此,似乎生成该类型的人正在为多态提升构造函数发出显式类型参数,但消费者希望它是隐式的。为了确认我更改了解决方法模块以使用单态数据类型List

data List
    = Nil
    | Cons ((Type -> Type) -> Type -> Type) List
Run Code Online (Sandbox Code Playgroud)

这又起作用了。

最后,我测试了中缀问题,只是为了确定,将其更改为:

data List
    = Nil
    | ((Type -> Type) -> Type -> Type) ::: List
Run Code Online (Sandbox Code Playgroud)

令我惊讶的是,它失败了,并出现了您熟悉的错误消息Operator applied to too few arguments。所以看来你发现了两个错误。有人应该理解多类但有人不理解类型运算符。我还没有深入挖掘,无法找出谁错了。