metronome-0.1.1: Time Synchronized execution.

Copyright(c) Paolo Veronelli 2012
LicenseBSD-style (see the file LICENSE)
Maintainerpaolo.veronelli@gmail.com
Stabilityunstable
Portabilitynot portable (requires STM)
Safe HaskellNone
LanguageHaskell98

System.Metronome.Practical

Contents

Description

A wrapper module around System.Metronome with easy functions.

In this snippet we run a metronome and attach 4 tracks to it.

First track ticks every 2 metronome ticks printing "." 5 times.

Second track ticks at each metronome tick. Forever it reads a string from a variable, it checks first track for actions finished, and push other 5 actions on the first, each printing the string read.

Third track ticks every 14 metronome ticks and forever modifies the string in the variable.

Fourth track ticks every 100 metronome ticks , it does nothing on first action , kill all tracks , including itself and the metronome, and wake up main thread on the second.

{-# LANGUAGE DoRec #-}

import System.IO
import System.Metronome.Practical
import Control.Concurrent.STMOrIO
import Control.Monad

main = do
      hSetBuffering stdout NoBuffering
      (m,f) <- dummyMetronome 0.1
      c <- dummyTrack f 2 0 $ replicate 5 $ return $ putStr "."
      v <- var "!"  
      c2 <- dummyTrack f 1 0 . repeat . noIO $ do
                as <- getActions c
                vl <- rd v
                when (null as) . setActions c . replicate 5 . return $ putStr vl
      c3 <- dummyTrack f 14 0 . repeat . noIO . md v $ map succ
      end <- chan ()
      rec {c4 <- dummyTrack f 100 0 . map noIO $ [return (), mapM_ kill [c,c2,c3,c4] >> kill m >> wr end ()]}
      mapM_ run [c,c2,c3,c4]
      rd end
      hSetBuffering stdout LineBuffering 

Synopsis

Thread

kill :: STMOrIO m => Control a -> m () Source

kill a thread

stop :: STMOrIO m => Control a -> m () Source

stop a thread

run :: STMOrIO m => Control a -> m () Source

run a thread

modRunning :: STMOrIO m => Control a -> m () Source

invert the running flag of a thread

Metronome

setTicks :: STMOrIO m => Control Metronome -> [MTime] -> m () Source

set the next ticking times for a metronome

modScheduled :: STMOrIO m => Control Metronome -> ([(Priority, Action)] -> [(Priority, Action)]) -> m () Source

change the actions scheduled for the next metronome tick

Track

modPhase :: STMOrIO m => Control Track -> (Ticks -> Ticks) -> m () Source

modify the ticks count from track start, shifting the next ticks relative to metronome ticks

setFrequency :: STMOrIO m => Control Track -> Frequency -> m () Source

set the track frequency

getActions :: STMOrIO m => Control Track -> m [Action] Source

read the remaining actions of a track

setActions :: STMOrIO m => Control Track -> [Action] -> m () Source

set the track actions

setPriority :: STMOrIO m => Control Track -> Priority -> m () Source

set a track priority

modMute :: STMOrIO m => Control Track -> m () Source

mute / unmute a track

Dummy

dummyMetronome Source

Arguments

:: MTime

time between ticks, in seconds

-> IO (Control Metronome, TrackForker)

metronome control structure and a function to fork tracks

create and fork a running metronome.

dummyTrack Source

Arguments

:: TrackForker

a track forking action from a metronome fork

-> Frequency

ratio of track ticks and metronome ticks

-> Priority

priority among the track peers

-> [Action]

actions to be executed, each on a separate track tick

-> IO (Control Track)

track control structure

create and fork a stopped track by a metronome

Practical

noIO :: STM () -> STM (IO ()) Source

no IO as result of the STM action