2

I'm trying to write a function like so:

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

but I can't get it to type check:

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

I've tried different things with ScopedTypeVariables and forall t. but I can't get it to work. How can I type check this function ?

[edit 1]

Adding the type signature

{-# 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

I get:

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

It's not easy to understand what is going on here... this is quite different from "normal" Haskell...

Final solution

{-# 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
miguel.negrao
  • 949
  • 5
  • 13

1 Answers1

1

You need to given an explicit type signature for your startRBMidi function, because it has a rank-2 type:

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

This is similar to the type of the compile function.

Essentially, this says that the argument function f needs to work for any starting time t.

Heinrich Apfelmus
  • 11,034
  • 1
  • 39
  • 67
  • You also need to add a type signature to `networkDesc`, because otherwise, GHC will infer a monomorphic type signature for the local `let` binding, which is not what you want. Again, `networkDesc` needs to work for all starting times `t`. – Heinrich Apfelmus Jun 01 '15 at 15:22
  • Great, that did it ! I have to say, for someone unfamiliar with Rank2Types and phantom types it's pretty much impossible to understand how to properly use the phantom parameter t. For those not using dynamic event switching it would be useful to have a simpler version of the library, although that off-course would be more work and more maintenance. thanks for the help ! – miguel.negrao Jun 01 '15 at 16:36
  • Fair enough. I intend to move away from the type parameter `t` because of such issues. See [issue #97](https://github.com/HeinrichApfelmus/reactive-banana/issues/97). – Heinrich Apfelmus Jun 04 '15 at 14:45