[Haskell-cafe] Re: Livecoding music in Haskell
Rohan Drape
rd at slavepianos.org
Wed Nov 8 06:17:53 EST 2006
On Tue Nov 7 16:32:11 EST 2006, alex wrote:
> The way I see it there are two big issues - the first is drift and the
> second is latency.
As hinted at when Alex's work was discussed last November:
"OSC messages can be timestamped, and SuperCollider has a sample
accurate scheduling queue, so language timing jitter can easily be
worked around."
http://www.haskell.org/pipermail/haskell-cafe/2005-November/012483.html
Currently Sound.SC3 has a procedure 'at' that can be used for
scheduling.
This procedure doesn't really belong in Sound.SC3, and ought probably
be taken out.
Still, with the current darcs repository the following makes a ping
every second, on the second, sample accurately, for half a minute. If
you run the binary twice the pings will be twice the amplitude, no
phase errors - fingers crossed.
import Sound.SC3
import Control.Concurrent (forkIO)
ping f a = out 0 (sinOsc AR f 0 * e)
where c = EnvNum (-4.0)
e = envGen KR 1 a 0 1 removeSynth (envPerc 0.1 0.6 1 [c,c])
latency = 0.01
bundle t m = OscB (t + latency) m
pinger = do now <- utc
at (fromIntegral (ceiling now)) f
where f t = do fd <- sc
send' fd (bundle t [s_new "ping" (-1) AddToTail 1])
putStrLn "Sending ping"
return 1.0
main = do fd <- sc
putStrLn "Sending Ping Instrument"
sync' fd (d_recv' "ping" (ping 440 0.1))
putStrLn "Resetting scsynth"
reset fd
putStrLn "Starting schedule thread"
forkIO pinger
putStrLn "Delaying main thread"
pause 30
putStrLn "End of delay, exiting"
The above assumes that scsynth is running on the local host at the
standard port, 57110, and that the GHC runtime scheduler jitter plus
localhost network latency for this task is below 0.01 seconds, which
is true on my otherwise idle X31 at 600MHz - this is not at all bad, I
am impressed in any case - setting latency to zero gives reports from
scsynth of:
> late 0.008414722
> late 0.006882722
> late 0.005348722
> late 0.003815721
> late 0.002282721
> late 0.000748721
Tacked on below, for interested readers, are some notes on a related
scheme scheduler, the notes were written in response to a related
query about scheme & scsynth some time ago. The relation to the
haskell above is pretty straightforward, the haskell 'at' discards the
notion of a mutable schedule - with cheap concurrency such a thing is
of arguable use - and the haskell 'at' ought to allow the event
generator to return Nothing to stop scheduling.
Regards,
Rohan
++
Simple sample accurate scheduling from runtimes with moderate
scheduling jitter is straightforward using SuperCollider.
One simple model is:
(at Q TIME (lambda (t f) (EVENT t) (f DELTA)))
at = the scheduler interface
Q = a <schedule> value
TIME = a UTC timestamp
t = the scheduled UTC time (ie. TIME or subsequent delta),
regardless of when the procedure actually runs
f = a rescheduling function that in effect does
(at Q (+ t DELTA) *SELF*)
EVENT = the action, usually constructs an osc bundle and
sends it to scsynth
DELTA = the delta time to reschedule to, to not re-schedule
just don't call f
The EVENT sends a bundle to scsynth and adds latency as required so
that the scheduled bundle arrives ahead of the timestamp, the actual
sample-accurate scheduling is handled by a queue at scsynth.
The example below will schedule a ping at each whole second, and the
scheduling will be sample accurate so long as the scheme runtime
jitter is less than 0.1 seconds minus the network latency to get a UDP
packet to the scsynth address.
Here (utc) gets the current time, (-> s p) sends an OSC packet p to
the server s, (/s_new ...) makes a /s_new OSC message, & (bundle t m)
makes an OSC packet converting the UTC timestamp to NTP.
(define s (open-udp* "127.0.0.1" 57110))
(define Q (make-schedule*))
(define L 0.1)
(define (ship t m) (-> s (bundle (+ t L) m)))
(at
Q (ceiling (utc))
(lambda (t f)
(ship t (/s_new "ping" -1 1 1))
(f 1.0)))
Obviously to schedule just one ping in five seconds time:
(at Q (+ (utc) 5) (lambda (t _) (ship t (/s_new "ping" -1 1 1))))
More information about the Haskell-Cafe
mailing list