csound-expression-opcodes-0.0.2: opcodes for the library csound-expression

Safe HaskellNone
LanguageHaskell98

Csound.Typed.Opcode.SignalIO

Contents

Synopsis

File I/O.

dumpk :: Sig -> Str -> D -> D -> SE () Source

Periodically writes an orchestra control-signal value to an external file.

Periodically writes an orchestra control-signal value to a named external file in a specific format.

 dumpk   ksig, ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/dumpk.html

dumpk2 :: Sig -> Sig -> Str -> D -> D -> SE () Source

Periodically writes two orchestra control-signal values to an external file.

Periodically writes two orchestra control-signal values to a named external file in a specific format.

 dumpk2  ksig1, ksig2, ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/dumpk2.html

dumpk3 :: Sig -> Sig -> Sig -> Str -> D -> D -> SE () Source

Periodically writes three orchestra control-signal values to an external file.

Periodically writes three orchestra control-signal values to a named external file in a specific format.

 dumpk3  ksig1, ksig2, ksig3, ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/dumpk3.html

dumpk4 :: Sig -> Sig -> Sig -> Sig -> Str -> D -> D -> SE () Source

Periodically writes four orchestra control-signal values to an external file.

Periodically writes four orchestra control-signal values to a named external file in a specific format.

 dumpk4  ksig1, ksig2, ksig3, ksig4, ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/dumpk4.html

ficlose :: D -> SE () Source

Closes a previously opened file.

ficlose can be used to close a file which was opened with fiopen.

 ficlose  ihandle
 ficlose  Sfilename

csound doc: http://www.csounds.com/manual/html/ficlose.html

fin :: Str -> D -> D -> [Sig] -> SE () Source

Read signals from a file at a-rate.

 fin  ifilename, iskipframes, iformat, ain1 [, ain2] [, ain3] [,...]

csound doc: http://www.csounds.com/manual/html/fin.html

fini :: Str -> D -> D -> [D] -> SE () Source

Read signals from a file at i-rate.

 fini  ifilename, iskipframes, iformat, in1 [, in2] [, in3] [, ...]

csound doc: http://www.csounds.com/manual/html/fini.html

fink :: Str -> D -> D -> [Sig] -> SE () Source

Read signals from a file at k-rate.

 fink  ifilename, iskipframes, iformat, kin1 [, kin2] [, kin3] [,...]

csound doc: http://www.csounds.com/manual/html/fink.html

fiopen :: Str -> D -> SE D Source

Opens a file in a specific mode.

fiopen can be used to open a file in one of the specified modes.

ihandle  fiopen  ifilename, imode

csound doc: http://www.csounds.com/manual/html/fiopen.html

fout :: Str -> D -> [Sig] -> SE () Source

Outputs a-rate signals to an arbitrary number of channels.

fout outputs N a-rate signals to a specified file of N channels.

 fout  ifilename, iformat, aout1 [, aout2, aout3,...,aoutN]

csound doc: http://www.csounds.com/manual/html/fout.html

fouti :: Str -> D -> D -> [D] -> SE () Source

Outputs i-rate signals of an arbitrary number of channels to a specified file.

fouti output N i-rate signals to a specified file of N channels.

 fouti  ihandle, iformat, iflag, iout1 [, iout2, iout3,....,ioutN]

csound doc: http://www.csounds.com/manual/html/fouti.html

foutir :: Str -> D -> D -> [D] -> SE () Source

Outputs i-rate signals from an arbitrary number of channels to a specified file.

foutir output N i-rate signals to a specified file of N channels.

 foutir  ihandle, iformat, iflag, iout1 [, iout2, iout3,....,ioutN]

csound doc: http://www.csounds.com/manual/html/foutir.html

foutk :: Str -> D -> [Sig] -> SE () Source

Outputs k-rate signals of an arbitrary number of channels to a specified file, in raw (headerless) format.

foutk outputs N k-rate signals to a specified file of N channels.

 foutk  ifilename, iformat, kout1 [, kout2, kout3,....,koutN]

csound doc: http://www.csounds.com/manual/html/foutk.html

fprintks :: Str -> Str -> [Sig] -> SE () Source

Similar to printks but prints to a file.

 fprintks  "filename", "string", [, kval1] [, kval2] [...]

csound doc: http://www.csounds.com/manual/html/fprintks.html

fprints :: Str -> Str -> [D] -> SE () Source

Similar to prints but prints to a file.

 fprints  "filename", "string" [, ival1] [, ival2] [...]

csound doc: http://www.csounds.com/manual/html/fprints.html

readk :: Str -> D -> D -> Sig Source

Periodically reads an orchestra control-signal value from an external file.

Periodically reads an orchestra control-signal value from a named external file in a specific format.

kres  readk  ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/readk.html

readk2 :: Str -> D -> D -> (Sig, Sig) Source

Periodically reads two orchestra control-signal values from an external file.

kr1, kr2  readk2  ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/readk2.html

readk3 :: Str -> D -> D -> (Sig, Sig, Sig) Source

Periodically reads three orchestra control-signal values from an external file.

kr1, kr2, kr3  readk3  ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/readk3.html

readk4 :: Str -> D -> D -> (Sig, Sig, Sig, Sig) Source

Periodically reads four orchestra control-signal values from an external file.

kr1, kr2, kr3, kr4  readk4  ifilname, iformat, iprd

csound doc: http://www.csounds.com/manual/html/readk4.html

Signal Input.

diskin :: Tuple a => Str -> Sig -> a Source

Deprecated. Reads audio data from an external device or stream and can alter its pitch.

ar1 [, ar2 [, ar3 [, ... arN]]]  diskin  ifilcod, kpitch [, iskiptim] \
          [, iwraparound] [, iformat] [, iskipinit]

csound doc: http://www.csounds.com/manual/html/diskin.html

diskin2 :: Tuple a => Str -> Sig -> a Source

Reads audio data from a file, and can alter its pitch using one of several available interpolation types, as well as convert the sample rate to match the orchestra sr setting.

Reads audio data from a file, and can alter its pitch using one of several available interpolation types, as well as convert the sample rate to match the orchestra sr setting. diskin2 can also read multichannel files with any number of channels in the range 1 to 24 in versions before 5.14, and 40 after. . diskin2 allows more control and higher sound quality than diskin, but there is also the disadvantage of higher CPU usage.

a1[, a2[, ... aN]]  diskin2  ifilcod, kpitch[, iskiptim \
          [, iwrap[, iformat [, iwsize[, ibufsize[, iskipinit]]]]]]

csound doc: http://www.csounds.com/manual/html/diskin2.html

in' :: Sig Source

Reads mono audio data from an external device or stream.

ar1  in  

csound doc: http://www.csounds.com/manual/html/in.html

in32 :: Tuple a => a Source

Reads a 32-channel audio signal from an external device or stream.

ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, ar13, ar14, \
          ar15, ar16, ar17, ar18, ar19, ar20, ar21, ar22, ar23, ar24, ar25, ar26, \
          ar27, ar28, ar29, ar30, ar31, ar32  in32  

csound doc: http://www.csounds.com/manual/html/in32.html

inch :: Tuple a => [Sig] -> a Source

Reads from numbered channels in an external audio signal or stream.

ain1[, ...]  inch  kchan1[,...]

csound doc: http://www.csounds.com/manual/html/inch.html

inh :: Tuple a => a Source

Reads six-channel audio data from an external device or stream.

ar1, ar2, ar3, ar4, ar5, ar6  inh  

csound doc: http://www.csounds.com/manual/html/inh.html

ino :: Tuple a => a Source

Reads eight-channel audio data from an external device or stream.

ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8  ino  

csound doc: http://www.csounds.com/manual/html/ino.html

inq :: (Sig, Sig, Sig, Sig) Source

Reads quad audio data from an external device or stream.

ar1, ar2,  ar3, a4  inq  

csound doc: http://www.csounds.com/manual/html/inq.html

inrg :: Sig -> [Sig] -> SE () Source

Allow input from a range of adjacent audio channels from the audio input device

inrg reads audio from a range of adjacent audio channels from the audio input device.

 inrg  kstart, ain1 [,ain2, ain3, ..., ainN]

csound doc: http://www.csounds.com/manual/html/inrg.html

ins :: (Sig, Sig) Source

Reads stereo audio data from an external device or stream.

ar1, ar2  ins  

csound doc: http://www.csounds.com/manual/html/ins.html

invalue :: Str -> Str Source

Reads a k-rate signal from a user-defined channel.

Reads a k-rate signal or string from a user-defined channel.

kvalue  invalue  "channel name"
Sname  invalue  "channel name"

csound doc: http://www.csounds.com/manual/html/invalue.html

inx :: Tuple a => a Source

Reads a 16-channel audio signal from an external device or stream.

ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, \
          ar13, ar14, ar15, ar16  inx  

csound doc: http://www.csounds.com/manual/html/inx.html

inz :: Sig -> SE () Source

Reads multi-channel audio samples into a ZAK array from an external device or stream.

 inz  ksig1

csound doc: http://www.csounds.com/manual/html/inz.html

mp3in :: Str -> (Sig, Sig) Source

Reads stereo audio data from an external MP3 file.

ar1, ar2  mp3in  ifilcod[, iskptim, iformat, iskipinit, ibufsize]

csound doc: http://www.csounds.com/manual/html/mp3in.html

soundin :: Tuple a => Str -> a Source

Reads audio data from an external device or stream.

Reads audio data from an external device or stream. Up to 24 channels may be read before v5.14, extended to 40 in later versions.

ar1[, ar2[, ar3[, ... a24]]]  soundin  ifilcod [, iskptim] [, iformat] \
          [, iskipinit] [, ibufsize]

csound doc: http://www.csounds.com/manual/html/soundin.html

Signal Output.

mdelay :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () Source

A MIDI delay opcode.

 mdelay  kstatus, kchan, kd1, kd2, kdelay

csound doc: http://www.csounds.com/manual/html/mdelay.html

monitor :: Tuple a => a Source

Returns the audio spout frame.

Returns the audio spout frame (if active), otherwise it returns zero.

aout1 [,aout2 ... aoutX]  monitor  

csound doc: http://www.csounds.com/manual/html/monitor.html

out :: Sig -> SE () Source

Writes mono audio data to an external device or stream.

 out  asig

csound doc: http://www.csounds.com/manual/html/out.html

out32 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () Source

Writes 32-channel audio data to an external device or stream.

 out32  asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8, asig10, \
          asig11, asig12, asig13, asig14, asig15, asig16, asig17, asig18, \
          asig19, asig20, asig21, asig22, asig23, asig24, asig25, asig26, \
          asig27, asig28, asig29, asig30, asig31, asig32

csound doc: http://www.csounds.com/manual/html/out32.html

outc :: [Sig] -> SE () Source

Writes audio data with an arbitrary number of channels to an external device or stream.

 outc  asig1 [, asig2] [...]

csound doc: http://www.csounds.com/manual/html/outc.html

outch :: Sig -> [Sig] -> SE () Source

Writes multi-channel audio data, with user-controllable channels, to an external device or stream.

 outch  kchan1, asig1 [, kchan2] [, asig2] [...]

csound doc: http://www.csounds.com/manual/html/outch.html

outh :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () Source

Writes 6-channel audio data to an external device or stream.

 outh  asig1, asig2, asig3, asig4, asig5, asig6

csound doc: http://www.csounds.com/manual/html/outh.html

outo :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () Source

Writes 8-channel audio data to an external device or stream.

 outo  asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8

csound doc: http://www.csounds.com/manual/html/outo.html

outq :: Sig -> Sig -> Sig -> Sig -> SE () Source

Writes 4-channel audio data to an external device or stream.

 outq  asig1, asig2, asig3, asig4

csound doc: http://www.csounds.com/manual/html/outq.html

outq1 :: Sig -> SE () Source

Writes samples to quad channel 1 of an external device or stream.

 outq1  asig

csound doc: http://www.csounds.com/manual/html/outq1.html

outq2 :: Sig -> SE () Source

Writes samples to quad channel 2 of an external device or stream.

 outq2  asig

csound doc: http://www.csounds.com/manual/html/outq2.html

outq3 :: Sig -> SE () Source

Writes samples to quad channel 3 of an external device or stream.

 outq3  asig

csound doc: http://www.csounds.com/manual/html/outq3.html

outq4 :: Sig -> SE () Source

Writes samples to quad channel 4 of an external device or stream.

 outq4  asig

csound doc: http://www.csounds.com/manual/html/outq4.html

outrg :: Sig -> [Sig] -> SE () Source

Allow output to a range of adjacent audio channels on the audio output device

outrg outputs audio to a range of adjacent audio channels on the audio output device.

 outrg  kstart, aout1 [,aout2, aout3, ..., aoutN]

csound doc: http://www.csounds.com/manual/html/outrg.html

outs :: Sig -> Sig -> SE () Source

Writes stereo audio data to an external device or stream.

 outs  asig1, asig2

csound doc: http://www.csounds.com/manual/html/outs.html

outs1 :: Sig -> SE () Source

Writes samples to stereo channel 1 of an external device or stream.

 outs1  asig

csound doc: http://www.csounds.com/manual/html/outs1.html

outs2 :: Sig -> SE () Source

Writes samples to stereo channel 2 of an external device or stream.

 outs2  asig

csound doc: http://www.csounds.com/manual/html/outs2.html

outvalue :: Str -> Sig -> SE () Source

Sends a k-rate signal or string to a user-defined channel.

 outvalue  "channel name", kvalue
 outvalue  "channel name", "string"

csound doc: http://www.csounds.com/manual/html/outvalue.html

outx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () Source

Writes 16-channel audio data to an external device or stream.

 outx  asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8, \
          asig9, asig10, asig11, asig12, asig13, asig14, asig15, asig16

csound doc: http://www.csounds.com/manual/html/outx.html

outz :: Sig -> SE () Source

Writes multi-channel audio data from a ZAK array to an external device or stream.

 outz  ksig1

csound doc: http://www.csounds.com/manual/html/outz.html

soundout :: Sig -> Str -> SE () Source

Deprecated. Writes audio output to a disk file.

The usage of soundout is discouraged. Please use fout instead.

 soundout   asig1, ifilcod [, iformat]

csound doc: http://www.csounds.com/manual/html/soundout.html

soundouts :: Sig -> Sig -> Str -> SE () Source

Deprecated. Writes audio output to a disk file.

The usage of soundouts is discouraged. Please use fout instead.

 soundouts   asigl, asigr, ifilcod [, iformat]

csound doc: http://www.csounds.com/manual/html/soundouts.html

Software Bus.

chani :: Sig -> SE Sig Source

Reads data from the software bus

Reads data from a channel of the inward software bus.

kval  chani  kchan
aval  chani  kchan

csound doc: http://www.csounds.com/manual/html/chani.html

chano :: Sig -> Sig -> SE () Source

Send data to the outwards software bus

Send data to a channel of the outward software bus.

 chano  kval, kchan
 chano  aval, kchan

csound doc: http://www.csounds.com/manual/html/chano.html

chn_k :: Str -> D -> SE () Source

Declare a channel of the named software bus.

Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.

  chn_k  Sname, imode[, itype, idflt, imin, ima, ix, iy, iwidth, iheight, Sattributes]

csound doc: http://www.csounds.com/manual/html/chn.html

chn_a :: Str -> D -> SE () Source

Declare a channel of the named software bus.

Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.

  chn_a  Sname, imode

csound doc: http://www.csounds.com/manual/html/chn.html

chn_S :: Str -> D -> SE () Source

Declare a channel of the named software bus.

Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.

  chn_S  Sname, imode

csound doc: http://www.csounds.com/manual/html/chn.html

chnclear :: Str -> SE () Source

Clears an audio output channel of the named software bus.

Clears an audio channel of the named software bus to zero. Implies declaring the channel with imode=2 (see also chn_a).

 chnclear  Sname

csound doc: http://www.csounds.com/manual/html/chnclear.html

chnexport :: Str -> D -> Str Source

Export a global variable as a channel of the bus.

Export a global variable as a channel of the bus; the channel should not already exist, otherwise an init error occurs. This opcode is normally called from the orchestra header, and allows the host application to read or write orchestra variables directly, without having to use chnget or chnset to copy data.

gival  chnexport  Sname, imode[, itype, idflt, imin, imax]
gkval  chnexport  Sname, imode[, itype, idflt, imin, imax]
gaval  chnexport  Sname, imode
gSval  chnexport  Sname, imode

csound doc: http://www.csounds.com/manual/html/chnexport.html

chnget :: Str -> SE Str Source

Reads data from the software bus.

Reads data from a channel of the inward named software bus. Implies declaring the channel with imode=1 (see also chn_k, chn_a, and chn_S).

ival  chnget  Sname
kval  chnget  Sname
aval  chnget  Sname
Sval  chnget  Sname

csound doc: http://www.csounds.com/manual/html/chnget.html

chnmix :: Sig -> Str -> SE () Source

Writes audio data to the named software bus, mixing to the previous output.

Adds an audio signal to a channel of the named software bus. Implies declaring the channel with imode=2 (see also chn_a).

 chnmix  aval, Sname

csound doc: http://www.csounds.com/manual/html/chnmix.html

chnparams :: Tuple a => a Source

Query parameters of a channel.

Query parameters of a channel (if it does not exist, all returned values are zero).

itype, imode, ictltype, idflt, imin, imax  chnparams  

csound doc: http://www.csounds.com/manual/html/chnparams.html

chnrecv :: Str -> SE Str Source

Recieves data from the software bus.

Receives data from a channel of the inward named software bus. Implies declaring the channel with imode=1 (see also chn_k, chn_a, and chn_S). Note that chnsendchnrecv (which in Csound6 work identically to invalueoutvalue) are usually used for the callback-based communication between Csound and an external host. Use the chnset/chnget opcodes for sending and receiving data inside Csound.

ival  chnrecv  Sname
kval  chnrecv  Sname
aval  chnrecv  Sname
Sval  chnrecv  Sname

csound doc: http://www.csounds.com/manual/html/chnrecv.html

chnsend :: D -> Str -> SE () Source

Sends data via the named software bus.

Send to a channel of the named software bus. Implies declaring the channel with imode=2 (see also chn_k, chn_a, and chn_S). Note that chnsendchnrecv (which in Csound6 work identically to invalueoutvalue) are usually used for the callback-based communication between Csound and an external host. Use the chnset/chnget opcodes for sending and receiving data inside Csound.

 chnsend  ival, Sname
 chnsend  kval, Sname
 chnsend  aval, Sname
 chnsend  Sval, Sname

csound doc: http://www.csounds.com/manual/html/chnsend.html

chnset :: D -> Str -> SE () Source

Writes data to the named software bus.

Write to a channel of the named software bus. Implies declaring the channel with imod=2 (see also chn_k, chn_a, and chn_S).

 chnset  ival, Sname
 chnset  kval, Sname
 chnset  aval, Sname
 chnset  Sval, Sname

csound doc: http://www.csounds.com/manual/html/chnset.html

setksmps :: D -> SE () Source

Sets the local ksmps value in an instrument or user-defined opcode block

Sets the local ksmps value in an instrument or user-defined opcode block.

 setksmps  iksmps

csound doc: http://www.csounds.com/manual/html/setksmps.html

xin :: Tuple a => a Source

Passes variables to a user-defined opcode block,

The xin and xout opcodes copy variables to and from the opcode definition, allowing communication with the calling instrument.

xinarg1 [, xinarg2] ... [xinargN]  xin  

csound doc: http://www.csounds.com/manual/html/xin.html

xout :: [Sig] -> SE () Source

Retrieves variables from a user-defined opcode block,

The xin and xout opcodes copy variables to and from the opcode definition, allowing communication with the calling instrument.

 xout  xoutarg1 [, xoutarg2] ... [, xoutargN]

csound doc: http://www.csounds.com/manual/html/xout.html

Printing and Display.

dispfft :: Sig -> D -> D -> SE () Source

Displays the Fourier Transform of an audio or control signal.

These units will print orchestra init-values, or produce graphic display of orchestra control signals and audio signals. Uses X11 windows if enabled, else (or if -g flag is set) displays are approximated in ASCII characters.

 dispfft  xsig, iprd, iwsiz [, iwtyp] [, idbout] [, iwtflg]

csound doc: http://www.csounds.com/manual/html/dispfft.html

display :: Sig -> D -> SE () Source

Displays the audio or control signals as an amplitude vs. time graph.

These units will print orchestra init-values, or produce graphic display of orchestra control signals and audio signals. Uses X11 windows if enabled, else (or if -g flag is set) displays are approximated in ASCII characters.

 display  xsig, iprd [, inprds] [, iwtflg]

csound doc: http://www.csounds.com/manual/html/display.html

flashtxt :: D -> Str -> SE () Source

Allows text to be displayed from instruments like sliders

Allows text to be displayed from instruments like sliders etc. (only on Unix and Windows at present)

 flashtxt   iwhich, String

csound doc: http://www.csounds.com/manual/html/flashtxt.html

print' :: [D] -> SE () Source

Displays the values init (i-rate) variables.

These units will print orchestra init-values.

 print  iarg [, iarg1] [, iarg2] [...]

csound doc: http://www.csounds.com/manual/html/print.html

printf_i :: Str -> D -> [D] -> SE () Source

printf-style formatted output

printf and printf_i write formatted output, similarly to the C function printf(). printf_i runs at i-time only, while printf runs both at initialization and performance time.

 printf_i  Sfmt, itrig, [iarg1[, iarg2[, ... ]]]

csound doc: http://www.csounds.com/manual/html/printf.html

printf :: Str -> Sig -> [Sig] -> SE () Source

printf-style formatted output

printf and printf_i write formatted output, similarly to the C function printf(). printf_i runs at i-time only, while printf runs both at initialization and performance time.

 printf  Sfmt, ktrig, [xarg1[, xarg2[, ... ]]]

csound doc: http://www.csounds.com/manual/html/printf.html

printk :: D -> Sig -> SE () Source

Prints one k-rate value at specified intervals.

 printk  itime, kval [, ispace]

csound doc: http://www.csounds.com/manual/html/printk.html

printk2 :: Sig -> SE () Source

Prints a new value every time a control variable changes.

 printk2  kvar [, inumspaces]

csound doc: http://www.csounds.com/manual/html/printk2.html

printks :: Str -> D -> [Sig] -> SE () Source

Prints at k-rate using a printf() style syntax.

 printks  "string", itime [, kval1] [, kval2] [...]

csound doc: http://www.csounds.com/manual/html/printks.html

prints :: Str -> [Sig] -> SE () Source

Prints at init-time using a printf() style syntax.

 prints  "string" [, kval1] [, kval2] [...]

csound doc: http://www.csounds.com/manual/html/prints.html

Soundfile Queries.

filebit :: Str -> D Source

Returns the number of bits in each sample in a sound file.

ir  filebit  ifilcod [, iallowraw]

csound doc: http://www.csounds.com/manual/html/filebit.html

filelen :: Str -> D Source

Returns the length of a sound file.

ir  filelen  ifilcod, [iallowraw]

csound doc: http://www.csounds.com/manual/html/filelen.html

filenchnls :: Str -> D Source

Returns the number of channels in a sound file.

ir  filenchnls  ifilcod [, iallowraw]

csound doc: http://www.csounds.com/manual/html/filenchnls.html

filepeak :: Str -> D Source

Returns the peak absolute value of a sound file.

ir  filepeak  ifilcod [, ichnl]

csound doc: http://www.csounds.com/manual/html/filepeak.html

filesr :: Str -> D Source

Returns the sample rate of a sound file.

ir  filesr  ifilcod [, iallowraw]

csound doc: http://www.csounds.com/manual/html/filesr.html

filevalid :: Str -> D Source

Checks that a file can be used.

Returns 1 if the sound file is valid, or 0 if not.

ir  filevalid  ifilcod

csound doc: http://www.csounds.com/manual/html/filevalid.html

mp3len :: Str -> D Source

Returns the length of an MP3 sound file.

ir  mp3len  ifilcod

csound doc: http://www.csounds.com/manual/html/mp3len.html