File: Run.hs

package info (click to toggle)
haskell-netwire 5.0.3-6
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 184 kB
  • sloc: haskell: 1,326; makefile: 2
file content (65 lines) | stat: -rw-r--r-- 1,680 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
-- |
-- Module:     Control.Wire.Run
-- Copyright:  (c) 2013 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>

{-# LANGUAGE RankNTypes #-}

module Control.Wire.Run
    ( -- * Testing wires
      testWire,
      testWireM
    )
    where

import Control.Monad.IO.Class
import Control.Wire.Core
import Control.Wire.Session
import Data.Functor.Identity
import System.IO


-- | This function runs the given wire using the given state delta
-- generator.  It constantly shows the output of the wire on one line on
-- stdout.  Press Ctrl-C to abort.

testWire ::
    (MonadIO m, Show b, Show e)
    => Session m s
    -> (forall a. Wire s e Identity a b)
    -> m c
testWire s0 w0 = loop s0 w0
    where
    loop s' w' = do
        (ds, s) <- stepSession s'
        let Identity (mx, w) = stepWire w' ds (Right ())
        liftIO $ do
            putChar '\r'
            putStr (either (\ex -> "I: " ++ show ex) show mx)
            putStr "\027[K"
            hFlush stdout
        loop s w


-- | This function runs the given wire using the given state delta
-- generator.  It constantly shows the output of the wire on one line on
-- stdout.  Press Ctrl-C to abort.

testWireM ::
    (Monad m', MonadIO m, Show b, Show e)
    => (forall a. m' a -> m a)
    -> Session m s
    -> (forall a. Wire s e m' a b)
    -> m c
testWireM run s0 w0 = loop s0 w0
    where
    loop s' w' = do
        (ds, s) <- stepSession s'
        (mx, w) <- run (stepWire w' ds (Right ()))
        liftIO $ do
            putChar '\r'
            putStr (either (\ex -> "I: " ++ show ex) show mx)
            putStr "\027[K"
            hFlush stdout
        loop s w