[haskell-art] recording scsynth

2007-07-23 Thread Rohan Drape
btw. for recording scsynth as it runs a jack recorder
can be simpler to manage, at least so i find.  i tend
to use jack.record + jack.plumbing, but there are
many others about.

darcs get http://slavepianos.org/rd/sw/sw-77/


___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


[Rohan Drape] Re: [Fwd: Re: [haskell-art] Re: Creating .wav or .aiff with SuperCollider/HSC3]

2007-07-24 Thread Rohan Drape
drat, different client same problem, sorry...

---BeginMessage---
Henning Thielemann [EMAIL PROTECTED] writes:
 what gives that error? hosc or hsc3 or scsynth?

 scsynth

ok, i'd guess that restriction could be trivially lifted 
for nrt but it is not usually an issue.  of course, in 
this case the size was probably off by 2^31 or so...

 try unreversed encode_i32 (osc tends to use sized integers,
 this is the case also for bundle sizes)

 Is the difference between u32 and i32, unsigned vs. signed?

yes, a typo in my message, replace sized with signed.

 Good to know.

perhaps... actually nrt in scsynth is very nice, what are 
ordinarily asynchronous operations become synchronous 
(eg. b_alloc and friends).  rt designs generally 'degrade' 
well to nrt use, the other direction tends to be a 
disaster area.
---End Message---
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


[haskell-art] Re: Creating .wav or .aiff with SuperCollider/HSC3

2007-08-10 Thread Rohan Drape
Henning Thielemann [EMAIL PROTECTED] writes:
 I boiled the problems down to a simple example. There are no errors
 reported about the messages, but the result is not what we expect.

I've added encodeNRT and writeNRT to hsc3, these
ought to work out of the box.  Let me know if
that helps.  (They are in Sound.SC3.Server.NRT, 
but exported from Sound.SC3.Server and Sound.SC3)

Regards,
Rohan
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] Re: Creating .wav or .aiff with SuperCollider/HSC3

2007-08-11 Thread Rohan Drape
Henning Thielemann [EMAIL PROTECTED] writes:
 We need
  encodeOSCZeroBase :: OSC - B.ByteString
   which converts a message by converting Double to Integer
   and does the message encoding (which is currently done by encodeOSC)
  delayOSC :: Double - OSC - OSC
   which shifts a message in time (i.e. changes time base)
  encodeOSC :: Double - OSC - B.ByteString
   calls delayOSC and encodeOSCZeroBase

 encodeOSCZeroBase can be used for non-realtime synthesis and encodeOSC for
 realtime use.

i'm not sure about this.  encodeOSC uses the conventional
'unix/utc' epoch.  encodeOSCZeroBase would not be 'zero' 
it would be the rather more obscure 'ntp epoch'.

it just happens that scsynth requires that nrt scores 
begin on the first of january 1900.  

i think a better idea would be to patch scsynth to work 
with relative timestamps so scores could start at any 
absolute time. (ie. at first january 1970, in which case
you could write scores starting at utc/unix zero).

rd
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] Re: Creating .wav or .aiff with SuperCollider/HSC3

2007-08-12 Thread Rohan Drape
Henning Thielemann [EMAIL PROTECTED] writes:
 But I indeed mean 'zero based'. Since scsynth doesn't know about Haskell's
 OSC type we can use any time base, and I think time base 0 is the most
 natural one. The actual time base needed for scsynth is added when
 encoding the message.

the meaning of the bundle timestamp is given by the
osc specification, not by scsynth.  hosc shifts the
epoch from 1900-01-01 to 1970-01-01 because that is
what system clocks use, and from a (32+32)bit integer
representation to a double because it makes the math
simpler.  this is, i think, pretty standard practice
in osc libraries.  in any case that is the hosc model.

 Today we write something like this
   do now - utc
  let msg = Bundle (now+effectStartTime) effect
  send fd (encodeOSC msg)

perhaps, however there are a _lot_ of ways to arrange 
scheduling, hosc and hsc3 are deliberately agnostic 
about this.

 This has also the advantage that generation of scores does not depend on a
 IO generated value (namely 'now').

osc does not have a notion of 'score'.  the scsynth 
notion is a minor abuse/extension of the osc protocol.
i imagine the scsynth requirement to start at ntp 
'zero' is so that scores do not need to contain a 
'nil' event if the initial 'actual' event is non-zero. 
(i'd prefer that scsynth accept any starting time, 
but can see both sides of that coin).

rd
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] Re: Creating .wav or .aiff with SuperCollider/HSC3

2007-08-13 Thread Rohan Drape
this all works here, apart from the fixed SR in the
audio file, which does not correspond to the SR that
scsynth runs at (-S doesn't seem to help, but 
whatever...)  

your osc file and the generated file are equal, 
at least according to cmp...

~$ cmp tone.osc ht-tone.osc 
~$

not sure what the matter can be, a bad scsynth seems
unlikely, but what else...  maybe we ought to take 
this off-list?
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] Creating .wav or .aiff with SuperCollider/HSC3 - crackles

2007-08-23 Thread Rohan Drape
Henning Thielemann [EMAIL PROTECTED] writes:
 I hoped that in non-realtime mode scsynth would simply generate the same
 sound as in the realtime mode, but there are crackles in the generated
 audio files. They look and sound like artifacts of too high elongations
 and probably different clipping handling in realtime (clipping) and
 non-realtime mode (wrap around). So I added `clip2 1` to the sound for
 manual clipping. But this doesn't help.

I've not had issues with scsynth in NRT mode, but
I've not tried writing integer files.

If you can make a test case against the current 
svn version perhaps submit a bug report?
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


[haskell-art] Re: SuperCollider: Is 'out' a typical UGen?

2007-09-14 Thread Rohan Drape
Dear Henning,

 Recently I had a bug in my program, which was due to adding 'out'
 twice to a UGen (however at different places). I thought it could be
 better to give UGens which have no output (in other words: UGens that
 cannot be input of other UGens), a different type. Say

 out :: UGen - UGen - Sink
 replaceOut :: UGen - UGen - Sink
 ...

 Would this work?

Perhaps, there are also 'Source' UGens, I'm
not sure the extra implementation complexity 
and uncertainty is worth-while.

In any case I've added a 'checkInputs' pass 
to the UGen constructor so that:

 out 0 (out 0 (sinOsc AR 440 0 * 0.1))

now generates an error.

| *** Exception: illegal inputUGen ...

Regards,
Rohan
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] OpenSoundControl: wait for multiple sends

2008-02-27 Thread Rohan Drape
Rohan Drape [EMAIL PROTECTED] writes:
 (and are biased to using many single threaded
 connections, hence wait design etc.)

that was a little terse, to clarify: 

wait in hosc discards any non-matching messages in the queue until it
receives the waited for message.  

error handling at sc3 is subtle.  

most commands can fail in some way, and if they do they send back a
/fail message.  if synchronous commands succeed they send nothing.
asynchronous commands will send back either a /done message at some
unknown time in the future, or a /fail message.

it is also possible to request various notification messages, which
can arrive at arbitrary times.

and bundles and cascaded errors make this more complicated still.

there are obviously many approaches to working with this.

sclang uses global shared state, which doesn't translate well to
haskell or to a many-lightweight-processes environment.

so, when using haskell i:

1. view /fail messages as fatal user error and don't attempt to
monitor them, instead relying on the scsynth stderr text to work out
what went wrong.

2. send all async commands using the hsc3 async function which is just
(send fd ...  wait fd /done).

wait ought to time out so that getting a /fail in place of a /done
does not hang the interpreter but there is a problem with the socket
library so the relevant code in hosc is commented out, see:

  http://www.haskell.org/pipermail/libraries/2005-October/004435.html

3. use separate threads for any notification monitoring (and only
monitor for /tr messages).

4. use a single short lived udp connection per 'interaction' with the
synthesiser.

the most notable problem with this approach is node  buffer id
management.

i think the correct way to address this is to write [s|g]_new 
b_alloc variants at scsynth that allocate a known unused identifier
and reply with an /id message.

it seems that it ought to be possible to make this fast enough, but
i'm not expert enough to know how, and it's not likely to interest the
sc3 people as they have the global-state-at-client solution all coded
up.

however, this'd allow for independent processes to safely use the
synthesiser.

at present one needs to have a separate process that allocates ids and
hope that all other processes go through that mechanism, which is a
pain  in any case unreliable in the general case.

(given the nature of the server the only process that actually
*definitely* knows what id's are in use when a _new/_alloc message
arrives is the server itself...)

rd
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] alsa-midi, midi, event-list, non-negative

2008-03-31 Thread Rohan Drape
alex,

On Tue, Apr 1, 2008 at 1:41 AM, alex [EMAIL PROTECTED] wrote:
  I'm planning on using a midi device in a performance on Friday, does
  anyone already have some example code for using this to control
  supercollider patchecs made with Rohan's HSC3, to save me a bit of time?
  If not I'll play around and try to provide this myself...

afraid i don't, so would like to see what you come up with.

i am still using an old kenton box via an old midi--osc
bridge for getting 7-bit controller data into scsynth.

in case all else fails some (away from desk so untested) example
code below, it ought to be close as is extracted from trivial
curses program that reads parameter names from a text file and
shows controller state in a terminal.  darcses at:

http://slavepianos.org/rd/sw/midi.osc/
http://slavepianos.org/rd/sw/tctl/

(midi.osc just sends the midi packets as osc blobs,
so pattern matching on the incoming packets is
actually pretty elegant, if you can remember the
midi constants, which i never can, the list i use is at
http://slavepianos.org/rd/sw/rsc3-midi/src/constants.scm)

regards,
rohan

++

import Control.Monad
import Sound.OpenSoundControl
import Sound.SC3

repeatM_ :: (Monad m) = m a - m ()
repeatM_ = sequence_ . repeat

-- extract 7-bit controller data packets
extract :: OSC - Maybe (Int, Int)
extract (Message /midi [Int _, Blob [0xb0, c, x]]) =
Just (fromIntegral c, fromIntegral x)
extract _ = Nothing

-- send 7-bit controller as (0,1) value
ctl :: Transport t = t - (Int, Int) - IO ()
ctl fd (i, x) = let { i_ = fromIntegral i
; x_ = fromIntegral x / 128.0 }
in send fd (c_set1 i_ x_)

main :: IO ()
main = do { m - openUDP 127.0.0.1 57150 -- midi.osc
  ; s - openUDP 127.0.0.1 57110 -- scsynth
  ; send m (message /receive [int 0x]) -- request notification
  ; repeatM_ (do { p - recv m
 ; maybe (return ()) (ctl s) (extract p) })

{-

let { c_in_l n (l, r) = linLin (lagIn 1 n 0.1) 0 1 l r
; c_in_x n (l, r) = linExp (lagIn 1 n 0.1) 0 1 l r
; f = c_in_x 0 (200, 600)
; a = c_in_l 1 (0, 0.1)
; l = c_in_l 2 (-1, 1) }
in audition (out 0 (pan2 (sinOsc AR f 0) l a))

-}
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art


Re: [haskell-art] [hsc3] soundIn

2008-04-21 Thread Rohan Drape
  great, thanks, mce is what i was looking for. am i correct in

there is a start of a sketch of the mce rules at:

http://slavepianos.org/rd/sw/hsc3/Help/hsc3.help.lhs

(ie. in the hsc3 sources, notes from never completed sc3 book effort)

  assuming that in' 2 AR 0 compiles to a single In ugen, while soundIn
  [0, 1] references two? what i meant was making the first argument to
  in' available as an argument to soundIn. reading consecutive input
  buses is a fairly common scenario ...

yes, correct, i've not optimised this to group conseuctive inputs,
i've never had enough input channels to notice the inefficiency, but
it can moderately easily be done,  i'd happily take a patch! if all
inputs are consecutive we can just use in' directly? are you thinking
of soundInN defined as:

   soundInN :: Int - UGen - UGen
   soundInN x n = in' x AR (numOutputBuses + n)

so that, ie. soundInN 3 (mce2 0 2) reads channel 2 twice?
perhaps it's just as clear to write soundIn (mce [0,1,2,2,3,4]) or
even soundIn (mce ([0..2]++[2..4]) )?

regards,
rohan
___
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art