如何解决 Reactive-banana 中 Moment t 的类型问题?

how to solve type issues with Moment t in reactive-banana?

我正在尝试编写如下函数:

module Main where

import Reactive.Banana
import Reactive.Banana.Frameworks


main = putStrLn "hello world"

type MIDIMessage = (Int, Int, Double)

startRBMidi f = do
    (addHandler, fire) <- newAddHandler :: IO (AddHandler MIDIMessage, Handler MIDIMessage)
    let
        networkDesc = do
            emidi <- fromAddHandler (addHandler :: AddHandler MIDIMessage)
            f emidi
    network <- compile networkDesc
    actuate network
    -- add fire to midi callbacks

但我无法对其进行类型检查:

ghc --make -O2 test.hs 
[1 of 1] Compiling Main             ( test.hs, test.o )

test.hs:17:24:
    Couldn't match type ‘t’ with ‘t1’
      because type variable ‘t1’ would escape its scope
    This (rigid, skolem) type variable is bound by
      a type expected by the context: Frameworks t1 => Moment t1 ()
      at test.hs:17:16-34
    Expected type: Moment t1 ()
      Actual type: Moment t ()
    Relevant bindings include
      networkDesc :: Moment t () (bound at test.hs:14:9)
      f :: Event t MIDIMessage -> Moment t () (bound at test.hs:11:13)
      startRBMidi :: (Event t MIDIMessage -> Moment t ()) -> IO ()
        (bound at test.hs:11:1)
    In the first argument of ‘compile’, namely ‘networkDesc’
    In a stmt of a 'do' block: network <- compile networkDesc

我用 ScopedTypeVariables 和 forall t 尝试了不同的东西。但我无法让它工作。我如何键入检查此功能?

[编辑 1]

添加类型签名

{-# LANGUAGE Rank2Types #-}
module Main where
import Reactive.Banana
import Reactive.Banana.Frameworks

main = putStrLn "hello world"

type MIDIMessage = (Int, Int, Double)

startRBMidi :: (forall t. Event t MIDIMessage -> Moment t ()) -> IO ()
startRBMidi f = do
    (addHandler, fire) <- newAddHandler :: IO (AddHandler MIDIMessage, Handler MIDIMessage)
    let
        networkDesc = do
            emidi <- fromAddHandler (addHandler :: AddHandler MIDIMessage)
            f emidi
    network <- compile networkDesc
    actuate network

我得到:

test.hs:18:22:
No instance for (Frameworks t0)
  arising from a use of ‘fromAddHandler’
The type variable ‘t0’ is ambiguous
Relevant bindings include
  networkDesc :: Moment t0 () (bound at test.hs:17:9)
Note: there is a potential instance available:
  instance Frameworks
             (reactive-banana-0.8.0.4:Reactive.Banana.Internal.Phantom.FrameworksD,
              t)
    -- Defined in ‘reactive-banana-0.8.0.4:Reactive.Banana.Internal.Phantom’
In a stmt of a 'do' block:
  emidi <- fromAddHandler (addHandler :: AddHandler MIDIMessage)
In the expression:
  do { emidi <- fromAddHandler
                  (addHandler :: AddHandler MIDIMessage);
       f emidi }
In an equation for ‘networkDesc’:
    networkDesc
      = do { emidi <- fromAddHandler
                        (addHandler :: AddHandler MIDIMessage);
             f emidi }

test.hs:20:24:
Couldn't match type ‘t0’ with ‘t’
  because type variable ‘t’ would escape its scope
This (rigid, skolem) type variable is bound by
  a type expected by the context: Frameworks t => Moment t ()
  at test.hs:20:16-34
Expected type: Moment t ()
  Actual type: Moment t0 ()
Relevant bindings include
  networkDesc :: Moment t0 () (bound at test.hs:17:9)
In the first argument of ‘compile’, namely ‘networkDesc’
In a stmt of a 'do' block: network <- compile networkDesc

理解这里发生的事情并不容易...这与 "normal" Haskell...

完全不同

最终解决方案

{-# LANGUAGE Rank2Types #-}
module Main where

import Reactive.Banana
import Reactive.Banana.Frameworks

main = putStrLn "hello world"

type MIDIMessage = (Int, Int, Double)

startRBMidi :: (forall t. Event t MIDIMessage -> Moment t ()) -> IO ()
startRBMidi f = do
    (addHandler, fire) <- newAddHandler :: IO (AddHandler MIDIMessage, Handler MIDIMessage)
    let
        networkDesc :: forall t. Frameworks t => Moment t ()
        networkDesc = do
            emidi <- fromAddHandler (addHandler :: AddHandler MIDIMessage)
            f emidi
    network <- compile networkDesc
    actuate network

您需要为您的 startRBMidi 函数提供明确的类型签名,因为它具有 rank-2 类型:

startRBMidi :: (forall t. Event t MIDIMessage -> Moment t ()) -> IO ()

这类似于compile函数的类型。

本质上,这表示参数函数 f 需要在任何开始时间 t 工作。