haskell - -ddump-simpl 是获得具体类型的最佳方法吗?

发布于 2024-12-13 18:52:50 字数 683 浏览 0 评论 0原文

我之前写过一个似乎可以工作的函数,但不幸的是我没有很好地编写代码,现在必须再次弄清楚[我正在修改我正在使用的 monad 变压器堆栈]。

run_astvn ::
    LowerMonadT (StateT LowerSketchData Identity) β
    -> Seq SketchAST
run_astvn x = get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
    where get_ast2 = snd . fst

我想获取 get_ast2 的具体类型。我似乎能够通过终端输出添加标志 -ddump-simpl 和 grep 直到我发现,(清理了一下)

(((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> Seq SketchAST

(抱歉,这对其他人来说可能是无意义的,但重点是它对我很有用。)有没有更快/更方便的方法来做到这一点?如果不是很明显,我在这种情况下所说的“具体”的意思是上面的类型是有用的;知道 snd 的类型。 fst 不是:)。

I had previously written a function that seems to work, but unfortunately I didn't write the code very nicely, and now have to figure it out again [that I'm modifying the monad transformer stack I'm working with].

run_astvn ::
    LowerMonadT (StateT LowerSketchData Identity) β
    -> Seq SketchAST
run_astvn x = get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
    where get_ast2 = snd . fst

I want to get the concrete type of get_ast2. I seem to be able to add the flag -ddump-simpl and grep through my terminal output until I find, (cleaned up a little)

(((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> Seq SketchAST

(Sorry this is likely nonsense to everyone else, but the point is it is useful for me.) Is there a faster / more convenient way to do this? In case it's not obvious, what I mean by "concrete" in this case is that the above type is useful; knowing the type of snd . fst is not :).

如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。

扫码二维码加入Web技术交流群

发布评论

需要 登录 才能够评论, 你可以免费 注册 一个本站的账号。

评论(2

奢欲 2024-12-20 18:52:50

目前我知道有两种方法可以做到这一点,它们都是黑客。第一种是使用隐式参数:

{-# LANGUAGE ImplicitParams #-}
import Control.Monad.State
import Control.Monad.Identity
import Data.Sequence
import qualified Data.Set as Set

data LowerSketchData = LowerSketchData (Set.Set Int)
type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
data SketchAST = SketchAST

--run_astvn ::
--    LowerMonadT (StateT LowerSketchData Identity) β
--    -> Seq SketchAST
run_astvn x = ?get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
--    where get_ast2 = snd . fst

然后,在 ghci 中:

*Main> :t run_astvn
run_astvn
  :: (?get_ast2::(((a, Seq a1), Seq a2), LowerSketchData) -> t) =>
     StateT
       (Seq a1) (StateT (Seq a2) (StateT LowerSketchData Identity)) a
     -> t

另一种方法是故意给出错误的类型签名并检查编译器如何抱怨。

import Control.Monad.State
import Control.Monad.Identity
import Data.Sequence
import qualified Data.Set as Set

data LowerSketchData = LowerSketchData (Set.Set Int)
type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
data SketchAST = SketchAST

run_astvn ::
    LowerMonadT (StateT LowerSketchData Identity) β
    -> Seq SketchAST
run_astvn x = get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
--    where get_ast2 = snd . fst
    where get_ast2 :: (); get_ast2 = undefined

这会给出错误:

test.hs:13:19:
    The first argument of ($) takes one argument,
    but its type `()' has none
    In the expression:
      <snip>

将错误的类型更改为 () -> ()

test.hs:13:30:
    Couldn't match expected type `()'
                with actual type `(((β, Seq SketchAST), Seq SketchAST),
                                   LowerSketchData)'
    In the second argument of `($)', namely
      <snip>

现在我们知道类型应该类似于 (((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> ()。最后一次迭代去掉了最终的(),因为编译器抱怨:

test.hs:13:19:
    Couldn't match expected type `Seq SketchAST' with actual type `()'
    In the expression:
      <snip>

...所以另一个 () 应该是 Seq SketchAST

There's two ways I know of to do this currently, and they're both sort of hacks. The first is to use implicit parameters:

{-# LANGUAGE ImplicitParams #-}
import Control.Monad.State
import Control.Monad.Identity
import Data.Sequence
import qualified Data.Set as Set

data LowerSketchData = LowerSketchData (Set.Set Int)
type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
data SketchAST = SketchAST

--run_astvn ::
--    LowerMonadT (StateT LowerSketchData Identity) β
--    -> Seq SketchAST
run_astvn x = ?get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
--    where get_ast2 = snd . fst

Then, in ghci:

*Main> :t run_astvn
run_astvn
  :: (?get_ast2::(((a, Seq a1), Seq a2), LowerSketchData) -> t) =>
     StateT
       (Seq a1) (StateT (Seq a2) (StateT LowerSketchData Identity)) a
     -> t

The other way is to give an intentionally wrong type signature and check how the compiler complains.

import Control.Monad.State
import Control.Monad.Identity
import Data.Sequence
import qualified Data.Set as Set

data LowerSketchData = LowerSketchData (Set.Set Int)
type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
data SketchAST = SketchAST

run_astvn ::
    LowerMonadT (StateT LowerSketchData Identity) β
    -> Seq SketchAST
run_astvn x = get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
--    where get_ast2 = snd . fst
    where get_ast2 :: (); get_ast2 = undefined

This gives the error:

test.hs:13:19:
    The first argument of ($) takes one argument,
    but its type `()' has none
    In the expression:
      <snip>

Changing the wrong type to () -> ():

test.hs:13:30:
    Couldn't match expected type `()'
                with actual type `(((β, Seq SketchAST), Seq SketchAST),
                                   LowerSketchData)'
    In the second argument of `($)', namely
      <snip>

So now we know the type should look like (((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> (). One last iteration gets rid of the final (), because the compiler complains that:

test.hs:13:19:
    Couldn't match expected type `Seq SketchAST' with actual type `()'
    In the expression:
      <snip>

...so the other () should be Seq SketchAST.

月隐月明月朦胧 2024-12-20 18:52:50

对编译器撒谎。添加错误的类型签名,然后它应该回复“无法将错误的类型与真实类型匹配”或当前的确切消息。

Lie to the compiler. Add a wrong type signature, then it should reply with 'Couldn't match wrong type with real type' or whatever the exact message currently is.

~没有更多了~
我们使用 Cookies 和其他技术来定制您的体验包括您的登录状态等。通过阅读我们的 隐私政策 了解更多相关信息。 单击 接受 或继续使用网站,即表示您同意使用 Cookies 和您的相关数据。
原文