在 reactimate 中执行 MonadIO 动作

Execute MonadIO action inside of reactimate

在 reactive-banana 中,我正在尝试 运行 reactimate :: Event (IO ()) -> Moment () hArduino packageArduino 的一些操作,MonadIO 的一个实例。包里好像没有提供Arduino a -> IO a的功能。您将如何在 reactimate 中执行 Arduino 操作?

我没有使用 Arduino 或 hArduino 的经验,所以请对接下来的内容持保留态度。

鉴于在每个 reactimate 上重新初始化电路板是不合理的,我认为没有一个干净的选择 [*]。根本问题是 reactimate 在 reactive-banana 中的实现对 Arduino monad 一无所知,因此它添加的所有额外效果必须在 reactimate 时解决触发动作(因此是 IO 类型)。我能看到的唯一出路是推出你自己的跳过初始化的 withArduino 版本。快速浏览一下 source,虽然很乱,但看起来可行。

[*] 或者至少是一个不涉及可变状态的干净选项,如正确的答案。


鉴于 Heinrich Apfelmus 通过提出一个有趣的出路来善意地补充了这个答案,我不得不实施他的建议。也归功于 gelisam,因为他的回答的脚手架为我节省了很多时间。除了代码块下方的注释之外,请参阅 Heinrich's blog 以获取对 "forklift".

的额外评论
{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables #-}

import Control.Monad (join, (<=<), forever)
import Control.Concurrent
import Data.Word
import Text.Printf
import Text.Read (readMaybe)
import Reactive.Banana
import Reactive.Banana.Frameworks

main :: IO ()
main = do
    let inputPin  = pin 1
        outputPin = pin 2

        readInputPin = digitalRead inputPin
        copyPin = digitalWrite outputPin =<< readInputPin

    ard <- newForkLift withArduino

    (lineAddHandler, fireLine) <- newAddHandler

    let networkDescription :: forall t. Frameworks t => Moment t ()
        networkDescription = do
            eLine <- fromAddHandler lineAddHandler

            let eCopyPin = copyPin <$ filterE ("c" ==) eLine
                eReadInputPin = readInputPin <$ filterE ("i" ==) eLine

            reactimate $ (printf "Input pin is on? %s\n" . show <=< carry ard)
                <$> eReadInputPin
            reactimate $ carry ard
                <$> eCopyPin

    actuate =<< compile networkDescription

    initialised <- newQSem 0
    carry ard $ liftIO (signalQSem initialised)
    waitQSem initialised

    forever $ do
        putStrLn "Enter c to copy, i to read input pin."
        fireLine =<< getLine

-- Heinrich's forklift.

data ForkLift m = ForkLift { requests :: Chan (m ()) }

newForkLift :: MonadIO m
            => (m () -> IO ()) -> IO (ForkLift m)
newForkLift unlift = do
    channel <- newChan
    let loop = forever . join . liftIO $ readChan channel
    forkIO $ unlift loop
    return $ ForkLift channel

carry :: MonadIO m => ForkLift m -> m a -> IO a
carry forklift act = do
    ref <- newEmptyMVar
    writeChan (requests forklift) $ do
        liftIO . putMVar ref =<< act
    takeMVar ref

-- Mock-up lifted from gelisam's answer.
-- Please pretend that Arduino is abstract.

newtype Arduino a = Arduino { unArduino :: IO a }
  deriving (Functor, Applicative, Monad, MonadIO)

newtype Pin = Pin Word8

pin :: Word8 -> Pin
pin = Pin

digitalWrite :: Pin -> Bool -> Arduino ()
digitalWrite (Pin n) v = Arduino $ do
    printf "Pretend pin %d on the arduino just got turned %s.\n"
           n (if v then "on" else "off")

digitalRead :: Pin -> Arduino Bool
digitalRead p@(Pin n) = Arduino $ do
    printf "We need to pretend we read a value from pin %d.\n" n
    putStrLn "Should we return True or False?"
    line <- getLine
    case readMaybe line of
        Just v -> return v
        Nothing -> do
            putStrLn "Bad read, retrying..."
            unArduino $ digitalRead p

withArduino :: Arduino () -> IO ()
withArduino (Arduino body) = do
    putStrLn "Pretend we're initializing the arduino."
    body

备注:

  • forklift(此处为ard)在单独的线程中运行Arduino循环。 carry 允许我们发送 Arduino 命令,例如 readInputPincopyPin 通过 Chan (Arduino ()).

    [=64 在这个线程中执行=]
  • 这只是一个名字,但无论如何 newForkLift 的参数被称为 unlift 很好地反映了上面的讨论。

  • 通信是双向的。 carry 工艺 MVar 使我们能够访问 Arduino 命令返回的值。这使我们能够以完全自然的方式使用 eReadInputPin 等事件。

  • 层次分明。一方面,主循环只触发 UI 事件,如 eLine,然后由事件网络处理。另一方面,Arduino代码只通过forklift与事件网络和主循环通信

  • 为什么我要放一个sempahore?我会让你猜猜如果你把它取下来会发生什么......

How would you execute Arduino actions in reactimate?

我会通过执行具有可观察到的副作用的 IO 操作来间接执行它们。然后,在 withArduino 中,我会观察到这个副作用和 运行 相应的 Arduino 命令。

这是一些示例代码。首先,让我们把导入移开。

{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables #-}

import Control.Monad.IO.Class
import Data.IORef
import Data.Word
import Reactive.Banana
import Reactive.Banana.Frameworks
import Text.Printf

由于我没有 arduino,我将不得不从 hArduino 中模拟一些方法。

newtype Arduino a = Arduino (IO a)
  deriving (Functor, Applicative, Monad, MonadIO)

newtype Pin = Pin Word8

pin :: Word8 -> Pin
pin = Pin

digitalWrite :: Pin -> Bool -> Arduino ()
digitalWrite (Pin n) v = Arduino $ do
    printf "Pretend pin %d on the arduino just got turned %s.\n"
           n (if v then "on" else "off")

digitalRead :: Pin -> Arduino Bool
digitalRead (Pin n) = Arduino $ do
    printf "We need to pretend we read a value from pin %d.\n" n
    putStrLn "Should we return True or False?"
    readLn

withArduino :: Arduino () -> IO ()
withArduino (Arduino body) = do
    putStrLn "Pretend we're initializing the arduino."
    body

在其余的代码中,我将假设 Arduino 和 Pin 类型是不透明的。

我们需要一个事件网络来将表示从 arduino 接收到的信号的输入事件转换为描述我们要发送到 arduino 的内容的输出事件。为了让事情变得非常简单,让我们从一个引脚接收数据并在另一个引脚上输出完全相同的数据。

eventNetwork :: forall t. Event t Bool -> Event t Bool
eventNetwork = id

接下来,让我们将事件网络连接到外部世界。当输出事件发生时,我只是将值写入 IORef,稍后我将能够观察到它。

main :: IO ()
main = do
    (inputPinAddHandler, fireInputPin) <- newAddHandler
    outputRef <- newIORef False

    let networkDescription :: forall t. Frameworks t => Moment t ()
        networkDescription = do
            -- input
            inputPinE <- fromAddHandler inputPinAddHandler

            -- output
            let outputPinE = eventNetwork inputPinE

            reactimate $ writeIORef outputRef <$> outputPinE
    network <- compile networkDescription
    actuate network

    withArduino $ do
      let inputPin  = pin 1
      let outputPin = pin 2

      -- initialize pins here...

      -- main loop
      loop inputPin outputPin fireInputPin outputRef

请注意 reactimatecompile 如何只在主循环之外调用一次。这些函数设置您的事件网络,您不想在每个循环中调用它们。

最后,我们 运行 主循环。

loop :: Pin
     -> Pin
     -> (Bool -> IO ())
     -> IORef Bool
     -> Arduino ()
loop inputPin outputPin fireInputPin outputRef = do
    -- read the input from the arduino
    inputValue <- digitalRead inputPin

    -- send the input to the event network
    liftIO $ fireInputPin inputValue

    -- read the output from the event network
    outputValue <- liftIO $ readIORef outputRef

    -- send the output to the arduino
    digitalWrite outputPin outputValue

    loop inputPin outputPin fireInputPin outputRef

请注意我们如何使用 liftIO 从 Arduino 计算内部与事件网络交互。我们调用 fireInputPin 来触发输入事件,事件网络导致输出事件被触发作为响应,而我们给 reactimatewriteIORef 导致输出事件的值被写入IORef。如果事件网络更复杂并且输入事件没有触发任何输出事件,则 IORef 的内容将保持不变。无论如何,我们可以观察该内容,并使用它来确定哪个 Arduino 计算 运行。在这种情况下,我们只需将输出值发送到预定的引脚。