ftp.nice.ch/pub/next/unix/music/cm.sd.tar.gz#/doc/dictionary.rtf

This is dictionary.rtf in view mode; [Download] [Up]

Common Music Dictionary

Heinrich Taube
Zentrum fuer Kunst und Medientechnologie
Ritterstr. 42  76137 Karlsruhe Germany
Email: hkt@zkm.de, hkt@ccrma.stanford.edu
Fax: +49 721 9340 39  Vox: +49 721 9340 300

___________________________________________________________________


accumulation				 [Item Stream Pattern Type]

accumulation implements a cumulative pattern in its data.  Each element is added to the set of elements that have been selected so far.  When all elements have been added the pattern repeats.

Example:

<cl> (setf x (notes c4 d e in accumulation))
#<ACCUMULATING-NOTE-STREAM 131656351> 

<cl> (loop repeat 2 collect (read-items x))
((C4 C4 D4 C4 D4 E4) (C4 C4 D4 C4 D4 E4))

See:
	cycle, function, graph, heap, palindrome, random, rotation,
	sequence

___________________________________________________________________


algorithm name type options &body body	[Macro]

algorithm creates or redefines an algorithm object.  An algorithm is a type of container that computes subobjects.  name is the name of the algorithm.  type is the class of object that the algorithm will compute.  options is a list of zero or more slot initialization pairs.  If no slots are to be initialized,  options should be the empty list ().  Otherwise, for each slot to be initialized (either in the algorithm or the data that it computes), its unquoted name is followed by its initial value.  The slot names are never evaluated, the values are always evaluated.  

The following slot initializations are available to all algorithms and generators:

length {integer}

The number of objects to create before stopping.  This may also be specified as events for backward compatibility.

start {number}

The local start time of the algorithm.  This may also be specified as time for backward compatibility.

end {number}

The local end time of the algorithm.

rhythm {number}

The time increment to the next run time of the algorithm.  The value of rhythm is automatically passed to the object created.

flags {bits}

The initial bit states for the algorithm.  It is normally not necessary to set these, but you may specify +compile+ to force compilation of the algorithm when it is defined.

The body of the algorithm consists of a sequence of Lisp forms that define the algorithm's behavior.  Statements in the body are executed in sequential order, each time the algorithm is scheduled to produce an element.  

Algorithm implements three extensions to standard Common Lisp syntax. First, slots in either the algorithm or the objects that it generates may be treated as if they were lexical variables within the scope of algorithm:

(algorithm foo midi-note (events 12 amplitude .1)
  (setf note (item (notes c4 d e f g)))
  (setf rhythm (between .1 .4))
	(setf duration rhythm))

Second, the item function supports several  keyword arguments that do not exist at top-level lisp.  Inside an algorithm, the item function is "redefined" as:

item  x &key :kill :alloc :chord :rest
	
These new keyword arguments have the following meaning:

:kill {t | integer | variable}

Controls whether or not the system terminates the algorithm when item returns :end-of-period as its state. If :kill is an integer, then the algorithm terminates after that many periods. 

:chord {t | nil}

Controls whether or not the system checks for chords. Defaults to t.

:rest {t | nil}

Controls whether or not the system checks for rests. Defaults to t.

:alloc {t | nil}

Controls whether or not the system allocates a variable to hold the item stream. Defaults to nil.

The third extension to standard Common Lisp syntax is the interpretation of item stream constructor macros such as (notes a4 b c) which appear within the scope of a call to the item function, as in:

(item (notes a4 b c) :kill t)

algorithm replaces these forms at run time with the item streams they create.   Since the body of an algorithm is executed each time a note is output, a form such as:

(setf note (item (notes c4 d e) :kill t))

would normally not have the intended effect of consecutively setting the freq     parameter to C4, D4, and E4. This is  because the notes macro creates a new item stream each time it is evaluated.  Normal Lisp evaluation of this example would access the first element of a new stream rather than accessing consecutive elements of a single, constant item stream.   This extension only applies to constructor macros written within the scope of a call to item inside algorithm and generator.  Constructor macros appearing in any other context will produce their normal results. This is a feature, not a bug!

Example:

(algorithm pulse midi-note (length 64 rhythm .1
                            duration .1)
  (setf note (item (notes c4 d ef f g af bf c5 
                          in random)))
  (setf amplitude (interpl (mod count 8) 
                           0 .25 7 .75)))

See:
		generator, name, vars, stella.rtf

___________________________________________________________________


amplitude amp &key :loudest :softest :power			[Function]

amplitude computes an amplitude value for the logical amplitude amp based on the values of the keyword arguments loudest  softest and power.  A logical amplitude is a floating point number between 0.0 and 1.0 or an amplitude symbol: pppp ppp pp p mp mf f ff fff ffff.  softest is the value to return when the logical amplitude is 0.0, and defaults to the global variable *amplitude-minimum*.  loudest is the value to return when the logical amplitude is 1.0, and defaults to the global variable *amplitude-maximum*. If softest and loudest are both integer values, then the value returned by amplitude will be coerced to an integer value.  This permits both floating point values and integer midi values to be calculated.  power is the power curve between softest and loudest, and defaults to the global variable *amplitude-power*.  amplitude computes its return value according to the formula:  softest+(loudest-softest)*amp^power.

Examples:

<cl> (loop for x from 0 to 1 by .25 
           collect (amplitude x))
(0.0 0.25 0.5 0.75 1.0)

<cl> (loop for a from 0 to 1 by .25 
           collect (amplitude a :power 2))
(0.0 0.0625 0.25 0.5625 1.0)

<cl> (loop for a in '(p mp f ff)
           collect (amplitude a :softest 0 
                                :loudest 127))
(42 56 84 98)

See:
	amplitudes, *amplitude-minimum*, 
	*amplitude-maximum*, *amplitude-power*

___________________________________________________________________


*amplitude-maximum*			                  [Global Variable]

*amplitude-maximum* is the default maximum value for the logical amplitude 1.0.  If *amplitude-maximum* and *amplitude-minimum* are both integers, then integer amplitude values are computed.  The default value of *amplitude-maximum* is 1.0

See:
	amplitude, amplitudes, *amplitude-maximum*, *amplitude-power		
___________________________________________________________________


*amplitude-minimum*			                  [Global Variable]

*amplitude-minimum* is default minimum value for the logical amplitude 0.0.  If *amplitude-maximum* and *amplitude-minimum* are both integers, then integer amplitude values are computed.  The default value of *amplitude-minimum* is 0.0.

See:
	amplitude, amplitudes, *amplitude-maximum*, *amplitude-power*

___________________________________________________________________


*amplitude-power*				  [Global Variable]

*amplitude-power* is the default power curve between logical amplitudes  0.0 and 1.0.  The default default value of *amplitude-power* is 1.0, which causes linear interpolation over the range of amplitudes. 

See:
	amplitude, amplitudes, *amplitude-maximum*, 		*amplitude-minimum*

___________________________________________________________________


amplitudes  {item}+ {option}*		 [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
softest {float | integer}
loudest {float | integer}
power {float}

Other options may be applicable based on {pattern}.

amplitudes creates an amplitude stream to return numerical amplitude values in a specified pattern.  Each element in an amplitude stream may be a logical amplitude or an item stream of logical amplitudes.  A  logical amplitude is a number between 0.0 and 1.0 or one of the amplitude symbols:  pppp ppp pp p mp mf f ff fff ffff.  

amplitudes implements the following constructor options:

softest {float | integer}

Sets the minimum return value of the stream when the logical amplitude is 0.0.   Defaults to the value of *amplitude-minimum*.

loudest {float | integer}

Sets the maximum return value of the stream when the logical amplitude is 1.0.   Defaults to the value of *amplitude-maximum*.

power {float}

Sets the power curve of the stream.  Defaults to the value of *amplitude-power*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x (amplitudes p mf mp fff in random for 8))
#<RANDOM-ITEM-STREAM 136712611> 

<cl> 
(read-items x)
(0.33333334 0.33333334 0.44444445 0.8888889 0.8888889 		    0.5555556 0.8888889 0.33333334) 

See:
	amplitude, *amplitude-minimum*,*amplitude-maximum*,
	*amplitude-power*

___________________________________________________________________


between lb ub &optional exclude state			[Function]

between returns a number greater than or equal to lb but less than ub.  If exclude is specified,  between avoids returning a value equal to it.  Exclude may be used to avoid direct repetition in random selection.  State should be a random state object, and defaults to the value of the global variable *cm-state*.

Examples:

<cl> (between 1 2)
1

<cl> (between 1 2.0)
1.234551

<cl> (loop with last repeat 10 
           collect (setf last (between 1 4 last))
(1 3 1 3 2 1 2 3 1 3)

See:
	pick, pickl
___________________________________________________________________


cents cents						[Function]

cents converts cents to a frequency scaler according to the formula: 

	(expt 10 (* cents (/ (log 2 10) 1200)))

 Example:

<cl> (cents 100)
1.0594631 

<cl> (note (* (pitch 'c4) (cents 1200)))
C5 
 
See:
	centify, defscale

___________________________________________________________________


centify scaler						[Function]

centify converts scaler to a cent value according to the formula: 

	(* (/ 1200 (log 2 10)) (log scaler 10))

 Example:

<cl> (centify (expt 2 1/24))

50.0 
 

    
See:
	cents, defscale

___________________________________________________________________


changes &key (:start  0) (:end  t) (:step 1) (:width 1)		[Macro]

changes creates one or more change values suitable to the rotation pattern's change option.  start, end, step, and width may be numbers or lists of numbers;   their values are "spread" across as many changes as are necessary to represent the longest list of values.  the  start, end, step, and width keywords may be specifed using either their keyword or symbol forms.

 Examples:

<cl> (changes)
(0 1 1) 

<cl> (setf x (changes start '(0 1) width 2))
#<CYCLIC-ITEM-STREAM 141064061>  

<cl> (read-items x)
((0 2) (1 2))

<cl> (setf x
       (items a b c d in rotation 
              change (changes start '(0 1) width 2)))
#<ROTATIONAL-ITEM-STREAM 123424>

<cl> (loop repeat 8 collect (read-items x))
((A B C D) (B A D C) (B D A C) (D B C A) (D C B A) (C D A B) (C A D B) (A C B D))  
 
    
See:
	rotation

___________________________________________________________________


chord &rest members					 [Macro]
[member+]					         [Read Macro]

chord (and the square bracket notation []) create chords out of members.  members may be either note, pitch or degree references.   Inside an algorithm chords are counted as single events.  The unless-chording macro may be used evaluate forms only once per chord, rather than once per chord member.

Example:

<cl> (setf x (pitches [c4 e g] [60 64 67]))
#<CYCLIC-PITCH-STREAM 133527221> 

<cl> (read-items x)
(261.62555 329.6276 391.99554 261.62555 329.6276 391.99554) 
    
See:
	unless-chording, status?, cm/doc/scales.rtf

___________________________________________________________________


CLM							[Syntax]

The CLM syntax implements score file and sound file generation for Common Lisp Music, a Lisp/DSP56000 sound synthesis package by William Schottstaedt at Stanford University (bil@ccrma.stanford.edu).

See:
	in-syntax, syntax

___________________________________________________________________


CMN							[Syntax]

The CMN syntax produces manuscript output using Common Music Notation, a Lisp music notation package developed by William Schottstaedt at Stanford University  (bil@ccrma.stanford.edu).

See:
	in-syntax, syntax

___________________________________________________________________


*cm-state*				                  [Global Variable]

*cm-state* is the default random state object used by Common Music.

___________________________________________________________________


*command-prompting*			                  [Global Variable]

*command-prompting* controls whether or not Stella will prompt for missing or illegal command line arguments.  If the value is t (the default), then command prompting is enabled, otherwise missing or illegal data results in an error message and an immediate return to the main Stella prompt.  Set *command-prompting* to nil if you prefer terse interaction.

___________________________________________________________________


*compile-algorithms*			                  [Global Variable]

*compile-algorithms* controls whether or not Stella attempts to compile algorithms and generators when they are defined.  The default value is nil.  If t, code is compiled if it results in a normal lambda expression,  otherwise the code runs interpreted.   Compiling might cause the definition process to take a bit longer, but execution speed may be many times faster.  You can force compilation of any particular algorithm by specifying flags +compile+ in the initialization arguments.

___________________________________________________________________


*coordinates-are-x-y-pairs*				[Global Variable]

*coordinates-are-x-y-pairs* determines how coordinates specified to interpolation or step-function are parsed.  If non-nil, coordinates are parsed as x,y pairs, otherwise they are parsed as y,x pairs.  The default value for *coordinates-are-x-y-pairs* is t.

Example:

<cl> (interpolation 0 0 50 .25 100 1)
(0 0 50 0.25 100 1) 

<cl> (setf *coordinates-are-x-y-pairs* nil)
NIL

<cl> (interpolation 0 0 .25 50 1 100)
(0 0 50 0.25 100 1) 

See:
	function-value, interpolation, step-function.

___________________________________________________________________


crescendo &rest options				               [Macro]

Options:
from {amplitude}
to {amplitude}
in {integer}
beat {amplitude)

crescendo returns a cyclic amplitude stream whose values start at from and move to to over in number of beats.   The options from, to and in are required.

Example:

<cl> (setf x (crescendo from p to fff in 12))
#<CYCLIC-ITEM-STREAM 131666241> 

<cl> (read-items x)
(0.4 0.44545454 0.49090907 0.5363636 0.58181816 0.6272727 0.6727273 0.71818185 0.7636364 0.809091 0.85454553 0.9000001) 

See:
	amplitude, amplitudes, diminuendo

___________________________________________________________________


CSound					      [Common Music Syntax]

The CSound syntax produces score files for C Sound, a sound synthesis package implemented in C.

See:
	in-syntax,  syntax

___________________________________________________________________


cycle					 [Item Stream Pattern Type]

cycle implements a cyclic pattern in its data.  Elements are selected in order, the last element loops back to the first.  cycle is the default pattern type if no in option is specified to an item stream constructor.

Example:

<cl> (setf x (rhythms q h e for 6))
#<CYCLIC-RHYTHM-STREAM 132666571> 

<cl> (read-items x)
(1.0 2.0 0.5 1.0 2.0 0.5) 

See:
	accumulation, function, graph, heap, palindrome, random, rotation,
	sequence

___________________________________________________________________


diminuendo &rest options				               [Macro]

Options:
from logical amplitude
to logical amplitude
in number

diminuendo returns a cyclic amplitude stream whose values move from a maximum specification to a minimum specification (inclusive) over a specified number of times. The options from to and in are required options diminuendo.

Example:

<cl> (setf x (diminuendo in 8 from .8 to .2))
#<CYCLIC-AMPLITUDE-STREAM 133753451> 

<cl> (read-items x)
(0.8 0.71428573 0.62857145 0.54285717 0.4571429 0.3714286 0.28571433 0.20000005) 

See:
	amplitude, amplitudes, crescendo

___________________________________________________________________


*default-midi-pathname* 	              				 [Variable]

*default-midi-pathname* is the default pathname for midi file operations.  All utilities merge user supplied pathnames with *default-midi-pathname* to form the fully specified pathname.  *default-midi-pathname* is initially set to "test.midi" in the  home directory (the value of (user-homedir-pathname))

___________________________________________________________________


defobject name supers slots		              			 [Macro]
	
defobject defines a new class of object.  name is the name for the new class.   supers is a list of one or more super classes for the new object.  Instances of the new class inherit all slots and methods defined on supers.   slots is a list of local slot specifications.  Each specification may be the name of a slot or a list:
	 (slot &key :initform :accessor :reader :writer)
Both keyword and symbolic forms of CLOS  :initarg slot options are automatically defined.  defobject  is a wrapper for Lisp's defclass macro that (may) also define methods for various system functions. For that reason, a defobject form should always be compiled.

___________________________________________________________________


defscale name (&key class number-of-octaves 		[Macro]
                                            lowest-pitch octave-ratio interval-ratio
                                            first-octave-number divisions-per-octave
                                            suboctave-enharmonic  superoctave-enharmonic)
&body prototype-octave)

defscale creates a scale object.   The system supports three different types of scale: equal tempered scales,  gapped scale, and general scales.  Equal tempered scales have a fixed ratio between scale degrees and scale octaves.  Gapped scales have a fixed ratio between octaves, but not between intervals within an octave.  General scales have no fixed ratio between either intervals or octaves; indeed, a general scale may not have octaves at all.  The type of scale that defscale creates is normally determined automatically through an examination of its keyword arguments and the forms in its body defining the  prototype octave.  Each form in the prototype octave is a definition of a prototype scale degree entry.  The actual scale degree entries are then computed by combining prototype octave information with the various keyword arguments supplied to the macro.  The full form for a prototype degree description is a list:
	 ((&rest note-names) &key :pitch :scaler :ratio)
where note-names are all the possible (enharmonic) note names for the degree and pitch, scaler, and ratio are mutually exclusive ways of specifying the floating point pitch in the prototype octave.  Use pitch to directly supply the floating point frequency of the entry.  Normally, its both easier (and safer) to specify the pitch indirectly, through either a scaler or a ratio value.  Scaler is a multiplier on the lowest-pitch keyword argument to defscale that produces the pitch of that entry.  The scaler value for the first entry should therefore be 1.0.  Ratio is the ratio distance to the next scale entry from the current one.  The ratio value for the last entry is ignored.  Ratio is really syntactic sugar;  the system automatically converts relative ratio distances to absolute scaler values.  There are two short cuts for defining scale degree entries:

If there is only one note name for an entry it is not necessary to specify that name as a list, so ((a) :scaler 1.2) is the same as (a :scaler 1.2)

If there is no scaler, pitch or ratio values (ie the scale is an equal tempered scale), then the surrounding list may be omitted, so (c cn) is the same as ((c cn)) and (c) is the same as c.

defscale supports the following keyword arguments:   

:class {equal-tempered-scale | gapped-scale | general-scale}

Specifies the class of scale to use for the new scale.  If the value is nil (the default) the class is automatically determined by defscale.

:lowest-pitch {float}

Specifies the lowest pitch (floating point frequency) for gapped or equal tempered scales. The pitch for each entry is then computed from lowest-pitch, octave-ratio (if any) and the various scaler or ratio values defined in the prototype octave.  

:number-of-octaves {integer | nil}

Specifies the number of octaves that the new scale is defined for.  A null value for number-of-octaves will produce a general scale.

:divisions-per-octaves {integer | nil}

Specifies the number of entries defined in the prototype octave.  If a general scale has multiple octaves, this value must be supplied.

:octave-ratio {number | nil}

Specifies the ratio between octaves (if any) in the scale.  A non-nil value produces either a gapped scale or an equal tempered scale, depending on whether or not scalars or ratios are present in the prototype octave.  A nil value for octave-ratio creates a general scale.

:interval-ratio {number}

Yet another way to specify equal tempered scales.  Normally not needed.   Defaults to octave-ratio^1/divisions-per-octave

:suboctave-enharmonic 

Specifies the note name that is enharmonic with the first degree in an octave.  

:superoctave-enharmonic

Specifies the note name that is enharmonic with the last degree in an octave.  

:first-octave-number {integer | |00|}

Specifies the first octave's counting index, which defaults to 0. If you want a 00 first octave, specify the symbol  '|00| as the value. 

Examples:

;; a 4 octave equal tempered scale, 5 notes per
;; octave, octaves slightly stretched:

<cl> (defscale foo (:lowest-pitch 123.45
                    :number-of-octaves 4
                    :octave-ratio 2.1)
       i ii iii iv v)
#<EQUAL-TEMPERED-SCALE Foo 137653271>

<cl> (in-scale 'foo)
#<EQUAL-TEMPERED-SCALE Foo 137653271>

<cl> (read-items (pitches i0 i1 ii2 iii3 v1))

(123.45 259.245 631.5002 1538.2844 469.33813) 

The definitions of many different types of scales may be found in the file "contrib/defscales.lisp"

See:
	find-scale, list-all-scales, cents, centify, *standard-scale*, 
	contrib/defscales.lisp

___________________________________________________________________


degree reference &optional scale			           [Function]

degree returns the integer scale position of  reference in scale. Reference may be a note (symbolic name), degree (integer scale position) or pitch (floating point frequency).

Examples:

<cl> (degree 'a4)
69

<cl> (degree 440.0)
69

<cl> (degree 69)
69

See:
	note, notes, pitch, pitches

___________________________________________________________________


degrees {item}+ {option}*			   [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
of {scale}
	
Other options may be applicable based on {pattern}.

degrees creates a scale degree stream to return the ordinal (integer) positions  of scale degree references in a specified pattern.   Scale degree references may be notes (symbol),  degrees (integer), pitches (float) or item streams of the same.

The constructors degrees, notes, pitches, intervals, and steps all implement the constructor option:

of {scale}

Sets the scale of  the stream.   Defaults to *standard-scale*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x (degrees c4 d e f in random for 8))
#<RANDOM-DEGREE-STREAM 131443131> 

<cl> (read-items x)
(65 64 64 60 65 62 64 64) 

See:
	notes, pitches, scales

___________________________________________________________________


doitems (var item-stream &key (periods 1)) &body body	[Iteration Macro]

doitems provides simple iteration over the items in an item stream.  It is an analogue to Lisp's dotimes and dolist iteration macros:  forms inside the body of doitems may reference var for the current item in the stream.  If var is a single variable it is bound to successive items in item-stream. If var is a  list of two variables, (var1 var2), then var1 is the iteration variable and var2 is the state variable.   Supplying a state variable allows forms to access the current state of the stream.  item-stream must evaluate to an item stream.  periods is the number of periods of item-stream to read, and defaults to 1.   

Example:

<cl> (doitems (x (items foo bar baz in random for 6))
       (format t " ~A" x))
 BAR FOO BAZ BAZ FOO BAZ

NIL

___________________________________________________________________


expr form					[Item Constructor]

expr creates an item for an arbitrary lisp expression (variables, function calls, etc) to be evaluated by the item function.  

Example:

<cl> (setf s (let ((x 0))
               (items 1 (expr (incf x)) for 20 )))

#<CYCLIC-ITEM-STREAM 133341111> 

<cl> (read-items s) 
(1 1 1 2 1 3 1 4 1 5 1 6 1 7 1 8 1 9 1 10) 

See:
	fn

___________________________________________________________________


fheader file &rest strings				[Function]

fheader sets the header of file to strings. fheader internally uses header on strings to return the full header for file.

Example:

<cl> (fheader "test.score" 
              "envelope afn = [(0,0) (.1,1)]"
              "include frobber.hdr")

#<File "test.score">
	
See:
	header

___________________________________________________________________


find-scale name &optional (mode :error) 			     [Function]

find-scale returns the scale named name.  if mode is :error an error is signaled if the scale does not exist. If mode is :ask, then find-scale returns nil if it cannot find the scale.

See:
	defscale, list-all-scales

___________________________________________________________________


fn function					[Item Constructor]

fn creates an item for a lisp function object to be evaluated by the item function. 

Example:

<cl> (setf s (items a 
                    (fn #'(lambda ()
                           (cons 1 (random 9))))))
#<CYCLIC-ITEM-STREAM 133341111> 

<cl> (read-items s 8)
(A (1 . 2) A (1 . 1) A (1 . 6) A (1 . 2)) 
 

See:
	expr

___________________________________________________________________


formatting-slots (object stream &rest global-directives) 		     [Macro]
                                  &body slot-directives

formatting-slots provides high level formatting control over printing the slot values of an object.  Its primary use is to facilitate method writing for Stella's two main output functions: print-object and write-event.  print-object methods are used  by commands such as List and Show to print a representation of an object to the terminal.  write-event methods are used by commands such as Write and Swrite to write slot values to scorefiles.

formatting-slots uses keyword formatting directives to control slot value displays.  A formatting directive may be either globally applied to all slots specified to formatting-slots or locally applied to a single slot.  Local directives always override global directives.

Global formatting directives appear as keyword argument following the object and stream parameters in the main argument list the macro:

object stream  &key (printer 'princ) (print-if t) eol prefix suffix format filter decimals
                             (delimiter #\space) preamble postamble constructor default)

Local directives are specified inside the body of formatting-slots.  A local directive may simply be the name of a slot, in which case all formatting information for that slot is taken from the global formatting directives, or a list in the form:

(slot &key (printer 'princ) (print-if t) (eol nil) prefix suffix  format filter decimals
                     delimiter constructor default)

As mentioned previously, local slot directives override global directives with the same name.   There are two exceptions to this rule.   :preamble and :postamble are global directives only, and may not be appear in a local directive at all.

Three special tokens, &key, &rest and &optional, may appear in the body of formatting-slots.  These provide a quick shorthand  for formatting slot values in "Lisp lambda list" format.  All slot directives appearing after &key will automatically contain a :print-if  directive value of :bound and a :prefix value that is the keyword name of the slot. For example,
	time &key amp (ampf :printer prin1)
would expand as the three slot directives:

	time
	(amp :print-if :bound :prefix ":AMP ")
	(ampf :print-if :bound :prefix ":AMPF " 
	      :printer prin1)

formatting-slots implements the following formatting directives:

:preamble {string | char}

Sets a string or character to be printed before any slot formatting occurs. 

:postamble {string | char}

Sets a string or character to be printed after all slot formatting occurs.

:delimiter {string | char}

Sets a string or char to be printed between each value. Defaults to #\Space. A globally specified  delimiter will not be printed before the first value or after the last value.

:print-if  {:bound | t | :always}

Controls when a slot should be processed.  If  t, the slot is formatted without any further checking.  An error is signaled if the slot is unbound at the time that its value should be printed.  This is useful for formatting required slot values to scorefiles because it detects incomplete score data at the earliest possible time.   If :print-if is :always, then if the slot is bound its value is formatted, otherwise the string "-unset-" is printed,  Use :print-if :always inside print-object methods to dusplay unbound slots in the object's display.  If  :print-if is :bound, then a slot value will be printed only if the slot has a value, and omitted from the display it does not.  Use  :print-if  :bound to print optional, keyword or message parameters.  All Music Kit slots format using :print-if  :bound and  :prefix set  to a MusicKit parameter message string.

:prefix {string | char | function}

Sets a string or chatacter to be printed after delimiter and before the valuet.  prefix must therefore include any delimiter between itself and the value to be printed.  If  prefix is a function, it is called at macroexpansion time to return the actual prefix string or character to be used.  The function is be passed one argument, the name of the slot to be prefixed.  The system predefines two prefix functions: keyword-prefix, which returns a string containing the Lisp keyword name of a slot and a trailing space, and music-kit-prefix, which returns the objective C message string  for a slot.

:suffix {string | char | function name}

Similar to prefix except that suffix is printed after the value.

:default {value | nil}

Provides a default value to be formatted if the slot is unbound.

:eol {t | nil}

Contols whether or not an end-of-line is printed after all other directives have been processed.  Defaults to  nil.

:printer {function name or lambda}

Sets the value printing function. The function is passed two arguments, the value to print and the output stream. The default printer is princ. 

:filter {function name or lambda}

Sets a function to be receive the value just before the value is printed.  :filter should therefore return the actual value :printer will print.

:decimals {integer | nil}

Creates a filter that checks for numeric values and rounds to integer places if it is.  If :integer is 0 then numeric values are coerced to integers.  :decimals and :filter are exclusive keywords.

:format {:quoted | :string | :careful}

Controls how a value should be formatted.   :quoted causes the single quote character ' to appear just before the printed value.  :string causes the value to be printed inside string quotes "".   :careful  cause the printing routine to check the value to be printed.  If the value is a list or an unbound symbol, it is quoted before printing, otherwise the value is printed exactly as it is.  :Careful may be used to print note names or instrument envelopes.  An envelope stored as an unquoted will be preceded by a quote when printed to score files but will also work when applied to a clm instrument directly.

:constructor {function}

Escape to user defined formatting via the supplied function.  The function is at macroexpansion time to return a function of one argument, which will receive the value from the slot.

Examples:

;; Music Kit

(formatting-slots (object stream :print-if :bound
                   :prefix mk-make-prefix)
   freq amp)

This causes the printed values of freq and amp to be delimited by a space (the default), and prefixed by their music kit message names.  A typical display might look like:

	"freq:c4 amp:.9"

;; Common Lisp Music 

(formatting-slots (obj stream :preamble "(fm-violin " 
                   :postamble ")" :eol t)
  time dur freq &key amp ampenv)

This prints the object in lisp "function call syntax", where the slots amp and ampenv are treated as lisp keyword values that only appear in the event if the slot is currently bound. A typical display might look like:

	"(fm-violin 0.0 1.0 440.0 .5 :ampenv '(0 0 1 100))"

___________________________________________________________________


function					[Item Stream Pattern Type]

The function pattern implements an escape to user defined pattern description.  A use supplied function is called whenever a new period's worth of items are needed. 

The function pattern type implements the constructor options:

with {function}

Sets the function  for the new stream.  The function may take any number of arguments and should returns two values: the list of items constituting the next period, and optional list of states corresponding to each item returned.  It is an error to return no elements.

args {arglist}

Sets the arguments passed to the function. Defaults to nil.

Example:

<cl> (let ((n 60))
       (setf x (notes in function
                      with #'(lambda () (incf n)))))

#<FUNCTIONAL-NOTE-STREAM 132004641> 

<cl> (read-items x 10)
(CS4 D4 DS4 E4 F4 FS4 G4 GS4 A4 AS4) 
 
See:
	accumulation, cycle, graph, heap, palindrome, random, rotation,
	sequence

___________________________________________________________________


function-value  x env &optional (scaler 1) (offset 0)	[Function]

function-value returns the y value of an x coordinate and an envelope. The y value is optionally scaled and offset according to the values of scaler and offset:
	 (y * scaler)+offset.

Example:

<cl> (setf x (interpolation 0 0 100 1))
(0 0 100 1) 

<cl> (function-value 50 x 2 3)
4.0 

See:
	interpolation, interpl, lookup, functions overview

___________________________________________________________________


generator name type options &body body	[Macro]

generator creates or redefines a generator object.   A generator is similar to an algorithm except that it saves the objects that it computes.  (An algorithm computes an object, but does not save it).  Generators are useful for algorithmic layout of material that is meant to be editable.

See:

	 algorithm, stella.rtf

___________________________________________________________________


graph					 [Item Stream Pattern Type]

The graph pattern arranges its data in nodes and traverses the graph be applying a selection function to each node in succession. A graph node is specified as a list:

(item  &key :to :id)

where item is the datum for the node,  id is a unique identifier for item, and to is a single id, a list of ids or an item stream of ids producing the id of the next node in the pattern.  If id is not supplied it defaults to item, but its always safer to explicitly provide a unique identifier.  The pattern is generated by applying a function to the current node to produce the to identifier of the next node in the pattern.  The default selection function works as follows.  If the node has only one to id, it returns the id.  If the node has a list of to ids, the function selects one at random.  If the node has an item stream of to ids, item is used to return the next id from the stream.  If the node does not not produce a next id, or if he id cannot be found in the graph, an error is signaled.   The first node in the graph data is the first node returned in the pattern.  to and id may be specifed as either keywords or symbols.

The graph pattern implements the following item stream constructor option:

with {function}

Sets the streams selection function which should takes two arguments:  the current node and the stream itself, and should return the id of the next node to be generated by the stream.  Defaults to a system defined selection function #'default-graph-node-select.

previous {number | id list}

Sets the number of previous node ids to pass to the selection function.  Useful for implementing Markov selection in graphs.  See idsel and "stella/example/markov.lisp" for more information about Markov selection.

Example:

<cl> (setf x (items (a to (a b c))
                    (b to (a c))
                    (c to (a)) in graph))
#<GRAPH-ITEM-STREAM 135506031> 

<cl> (read-items x 10)
(A B C A A B A A B C) 

See:
	accumulation, cycle, function, heap, palindrome, random, rotation,
	sequence, idsel

___________________________________________________________________


header &rest strings				[Function]

header treats each string in strings as a line to be included in the header of a scorefile.  header returns the concatenation of strings with a #\NewLine character automatically appended to the end of each string 

Example:

<cl> (header "envelope afn = [(0,0) (.1,1)]"
             "include frobber.hdr")

"envelope afn = [(0,0) (.1,1)]
include frobber.hdr
" 
	
See:
	fheader 

___________________________________________________________________


heap					 [Item Stream Pattern Type]

The heap pattern arranges its data as a "deck of cards" that gets reshuffled after all elements have been "dealt".   The order of elements is therefore unpredictable but the set of elements is exhaustively generated each cycle through the data.

Example:

<cl> (setf x (notes c4 d e f in heap for 12))
#<HEAP-NOTE-STREAM 132054701> 

<cl> (read-items x)
(C4 E4 D4 F4 C4 F4 E4 D4 C4 D4 E4 F4) 

See:
	accumulation, cycle, function, graph, heap, palindrome, random, rotation, sequence 

___________________________________________________________________


heap name options &body body	 [Macro]


The heap macro creates a heap container object A heap is a type of thread that, when called upon to produce its objects, first shuffles them to produce a random ordering.  The syntax of the heap heap macro is exactly the same as for thread. 
	

See:
	thread, stella.rtf

___________________________________________________________________


#ipd()	 						[Read Macro]


The #i read macro implements a short hand for item stream definition.  The pattern and data type of a stream  may be specified by two optional qualifying characters pd to the macro.   The qualifying character p determines the pattern type of the stream.  If the pattern character is not specified the pattern type defaults cycle.  The second qualifying character d determines the data type of the stream, which defaults to item if the character is not specified.  The list of items and options directly follow the #ipd declaration.

	Pattern Characters 	Data Characters
	C = Cycle		N = Note
	R = Random		R = Rhythm
	H = Heap			P = Pitch
	G = Graph		D = Degree
	S = Sequence		I = Interval
	A = Accumulation		S = Step
	P = Palindrome		A = Amplitude
	F = Function		X = Item (not needed)

Examples:

Cyclic item stream:	#i(a b c)
Random item stream:	#ir(a b c)
Heap note stream:		#ihn(a3 b c for 10)	
Random rhythm stream:	#irr(q (w weight .2) e)

___________________________________________________________________


idsel  [{id+} {stream}]+					[Macro]

idsel may be used in conjunction with graph nodes and the graph option previous to create transition tables for Markov processing.  A transition table is specified as a sequence of node ids and probability stream descriptions.   {id+} may be a single id or a list of previous number of ids; {stream} is the probability stream to use if {id+} matches the previously selected ids.   For example, a node of a 2nd order Markov graph might have the following idsel:

	(idsel a (items a b c in random) 
	       b (items (a weight 4) b in random)
	       c a))

which would correspond to the transition table portion:

                   Current+Last
	             A    B    C
	             B    B    B
	        A  .333  0.0  1.0
	Next    B  .333  .25  0.0
	        C  .333  .75  0.0

idsel uses pattern matching to look up the previous id choices in the selection table.  This means that selection tables need not be fully enumerated and that "wildcard" selection is possible.  Previous ids are matched with candidate {id+} descriptions using the following two rules:

Matching occurs for the length of {id+}, which may be less than previous.   If every {id+} matches its corresponding position in previous, then that table entry is selected.  This allows multiple entries in a table to be collapsed to a single selection.

A * at any position in {id+} matches the corresponding previous choice, no matter what it was.  For example, the following two selection tables are equivalent:

        (idsel a (items a b c d in random)
               b (items (a weight 4) c d in random)
               c (items a b c d in random)
               d (items a b c d in random))

        (idsel b (items (a weight 4) c d in random)
               * (items a b c d in random))

___________________________________________________________________


infiles  file &rest more-files					[Function]

infiles returns a list of  input sound file names for use with an RT output stream.  file is a string file name or file names delimited by comma.  more-files is any number of additional file names. infiles treats directories as "sticky", so only the first file in a directory need contain the directory component.  The default directory is "~/" and the default file extension is ".snd".

Example:

<cl> (infiles "aa" "snd/bb" "cc")

(#p"/user/hkt/aa.snd" #p"/user/hkt/snd/bb.snd" #p"/user/hkt/snd/cc.snd")

Stella: {open foo.rt infiles (infiles "aa" "snd/bb" "cc") 
                     outfile "/tmp/xx.snd"}
	
 ___________________________________________________________________


in-scale name					           [Function]

in-scale sets the global default scale to a new scale.The function takes one argument, name, which should be the name of the new scale.  in-scale may be used inside defscorefile to set the default scale for the score file. A scale specified to a note stream will locally override the global scale specified by in-scale.  in-scale's effects are undone once the defscorefile terminates.  The initial scale value in Common Music is the standard chromatic scale.

See:
	defscale, *standard-scale*

___________________________________________________________________


in-syntax syntax 					           [Function]

in-syntax sets the current score output syntax for Common Music.  syntax should be one of the predefined syntaxes: CLM, MusicKit, CSound, MIDI or their keyword equivalents.  in-syntax may be used in init files to set the initial syntax when lisp first boots up.  If no current syntax is set when a score is created the system will automatically prompt for the syntax to use.  This syntax will become the default syntax for further score creation.

See:
	*syntax*, :syntax

___________________________________________________________________


in-tempo tempo &optional beat			[Function]

in-tempo sets the global default tempo to a new tempo.The function takes two arguments, tempo, which should be the metronome value of the new tempo, and beat, which determines the of rhythmic value of the pulse.  The value of beat may be any rhythm symbol, if none is specified the default value is quarter note.

 in-tempo may be used inside defscorefile to set the default tempo for the score file.  A tempo specified to a rhythm stream will locally override the global tempo specified by in-tempo.  in-tempo's effects are undone once the defscorefile terminates.  The initial tempo value is 60.

Example:

<cl> (in-tempo 120 'q.)



See:
	rhythms, tempo, *standard-tempo*

___________________________________________________________________


interpl x &rest coords				  [Function]

interpl computes the interpolated value of x in coords, where coords is a sequence of x,y values.

Example:

<cl> (interpl 75 0 0 50 .5 100 0)
.25

See:
	function-value, lookup

___________________________________________________________________


interpolation &rest coords				               [Macro]

interpolation creates an interpolating envelope from the specified x,y coordinates.  The global variable *coordinates-are-x-y-pairs* controls the parsing order coordinate pairs.  The default setting t means that the system expects the coordinates to be in x,y order.

Example:

<cl> (setf x (interpolation 0 0 50 .5 100 0))
(0 0 50 0.5 100 0) 

<cl> (function-value 75 x)
0.25 

See:
	function-value, interpl, lookup

___________________________________________________________________


intervals {item}+ {option}*			   [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
of {scale}
from {scale degree reference}
on {scale degree reference}
initially-from {scale degree reference}
linked-to {name}
returning {note | pitch}

Other options may be applicable based on {pattern}.

intervals creates an interval stream to return integer intervals in a specified pattern.  An interval describes a relative distance in a scale, as opposed to the absolute  notes, degrees or pitches of a scale.  Each interval in the data may be an integer or an item stream that produces integers.  If an optional transposition offset is provided, the values generated by the stream will be transposed to that offset.  The offset may be specified as a note (symbol), pitch (float), degree (integer) or an item steam of the same.  If provided, an offset is reset either once each period or once each read depending on whether it is specified using the from or on options.  intervals can be coerced to return either symbolic note names or floating point pitches by using the returning option.

The intervals and steps constructors implement the constructor options:

from {scale degree reference | stream}

Sets the transposition offset of the stream, which defaults to 0.  The transposition offset is reset once each period.  from,  on, initially-from and linked-to are mutually exclusive options.

on  {stream}

Similar to from except that the transposition value is read in parallel with the pattern selection.   from,  on, initially-from and linked-to are mutually exclusive options. 

initially-from {scale degree reference}

Similar to from except that the transposition offset is never reset, so subsequent periods start where the previous ones left left off.  from,  on, initially-from and linked-to are mutually exclusive options.

linked-to {stream name}

Sets the transposition value as the current transposition value of some other stream. The name of the stream is not quoted.   from,  on, initially-from and linked-to are mutually exclusive options.

returning {note | pitch | degree}

Coerces the interval stream to return symbolic note names or floating point frequencies.  

of {scale}

Sets the scale of  the stream.   Defaults to *standard-scale*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Examples:

<cl> (setf x 
       (intervals 1 2 3 4 5 in random 
                  from 'c4 for 8 returning note))
#<RANDOM-INTERVAL-NOTE-STREAM 136751211> 

<cl> (read-items x)
(DS4 CS4 CS4 DS4 D4 DS4 DS4 E4)

<cl> (setf x (intervals 0 1 2 
               initially-from 'c4 returning note))
#<CYCLIC-INTERVAL-NOTE-STREAM 137126731> 

<cl> (read-items x)
(C4 CS4 D4) 

<cl> (read-items x)
(D4 DS4 E4)

<cl> (setf x (notes (notes c3 c4 for 1 named foo)
                    (intervals 1 2 linked-to foo)))
#<CYCLIC-NOTE-STREAM 137175041> 

<cl> (read-items x)
(C3 CS3 D3) 

<cl> (read-items x)
(C4 CS4 D4) 


See:
	steps

___________________________________________________________________


item stream						[Function]
item stream &key :kill :chord :rest :alloc	        [algorithm Special Form]
	    

item returns the next element from stream, and a flag indicating if stream is at :end-of-period as a result of the read.  As with all multiple values in Lisp, the second value may be ignored.

Example:

<cl> (setf x (items foo))
#<CYCLIC-ITEM-STREAM 133134441> 

<cl> (item x)
FOO 
:END-OF-PERIOD 

See:
	items, item streams

___________________________________________________________________


items  {item}+ {option}*			   [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}

Other options may be applicable based on {pattern}.

items creates a basic item stream.  A basic item stream returns its elements in a specified pattern.  Each item in a basic item stream may 
either be an element in the stream or an embedded item stream.

All item stream constructors implement the following options:

in {pattern} 

Sets the pattern type of the stream, which defaults to cycle. Other possible patterns include:  accumulation, function, graph, heap, palindrome, random, rotation and sequence.

for {integer | stream}

Sets the period length of the stream, which defaults to a pattern specific length.  The length of a period may be any non-negative number, including 0, and is reset once each period.  If the period length is set to 0, then the stream will be omitted from its superior stream's  pattern until the stream is reselected and it sets its period length to a number greater than 0.  The period length either counts subperiods or values in the pattern's data, depending on the value of the counting option. 

counting {periods | values}

Controls whether the period length of the stream counts periods in the pattern or values returned in the pattern.  If  periods (the default) , the number of elements returned in the period is the sum of that many period lengths in the data.  If values, the number of elements returned is the same as the period length.

traversing {depth | breadth}

Controls whether the pattern visits its items in depth first or breadth first order.   If depth (the default) , the pattern is only incremented when the current element is at :end-of-period.  If breadth, the pattern is incremented after each read.  (traversing breadth could also be implemented by setting the period lengths of all substreams to 1, but this would be much less efficient).

named {name}

Sets name to be the name of the item stream.  A named item stream may be subsequently referenced using #@ or motive.  

Example:

<cl> (setf x (items This is a sentence! in heap))
#<HEAP-ITEM-STREAM 133137601> 

<cl> (read-items x)
(A SENTENCE! THIS IS) 

See:
	notes, degrees, pitches, rhythms, intervals,
	steps

___________________________________________________________________


list-all-scales		 			     [Function]

list-all-scales returns a list of all scale objects currently defined in the system. 

See:
	defscale, list-all-scales

___________________________________________________________________


*listing-length*					     [Global Variable]

*listing-length* determines the number of objects that the List command shows for unqualified (unbounded) listings.  The default value of *listing-length* is 50.

___________________________________________________________________


lookup x values					           [Function]

lookup returns the uninterpolated y value of x in values.  Since the y value is not used by lookup it does not have to be a number.

Example:

<cl> (lookup 75 '(0 moe 50 curley 100 larry))
CURLEY

See:
	tempo-function, function-value, interpl

___________________________________________________________________


make-item-stream datatype pattern items &rest keywords	[Function]
	
make-item-stream creates an item stream for the specified datatype, pattern, items, and keyword arguments.  make-item-stream is a low level function that is normally not  necessary to use.  However, if the standard constructor macros do not permit enough control over the evaluation of data, make-item-stream will evaluate  all data and options according to normal Lisp rules.  Datatype is the name of the constructor macro that make-item-stream is replacing (items, notes, etc), pattern is the pattern to produce items in (cycle, heap, etc) and keywords are the lisp keyword equivalents of the constructor options.

___________________________________________________________________


map-data  function item-stream			           [Function]

map-data maps function over the data in an item stream.  Function is a function of one argument that map-data funcalls on each successive item in the stream.  

Warning: Some item stream data are internally represented in a canonical form different than the form specified by the user.

Examples:

(defun stream-list (stream)
  (let ((l '()))
    (map-items #'(lambda (x) (push x l))
               stream)
    (nreverse l)))

(defun stream-elements (stream)
  (let ((l '()))
    (map-items #'(lambda (x) 
                    (if (typep x 'item-stream)
                        (push (stream-elements x) l)
                        (push x l)))
               stream)
    (nreverse l)))

___________________________________________________________________


*mapping-level*					  [Global Variable]

*mapping-level* controls the depth to which containers are recursively visited when mapped by commands such as Set, Transpose and Map.  The value may be a number or T, in which case full recursion is enabled.  The default value of *mapping-level* is 1, which means that subobjects but not subcontainers of the mapped container are visited.

___________________________________________________________________


*mapping-mode*					  [Global Variable]

*mapping-mode* determines the type of object mapped by commands such as Set, Transpose and Map.  The value may be :data or :containers.  The default value of *mapping-mode* is :data.

___________________________________________________________________


merge name options &body body	[Macro]

The merge macro creates or redefines a merge object.  A merge is a type of collection  that arranges and access its sub objects in parallel order, by processing them in a scheduling queue.  name is the name for the new merge.  options is a list of zero or more slot initializations in the form of slot and value pairs.  Currently, the only initialization you should supply for a merge or thread is start.  If start is specified it becomes the permanent start time for the object.  Following the options list comes the body of the merge definition.  Any lisp code is legal here.  Normally, this code would create the containers that are to be executed inside the merge.  Objects created inside the body of the merge definition will automatically be added to the merge in the order they were created.  

Example:

(merge test-merge ()
  (thread sub1 () 
    (element midi-note note 'c3 rhythm .5 duration 1
             amplitude .7)
    (element midi-note note 'fs3 rhythm 2 duration 2 
             amplitude .7))
    (let ((rhy .1)(dur .2)(amp .5))
      (thread sub2 () 
        (doitems (x (notes c4 d ef f g in random 
                                       for 10))
           (element midi-note note x rhythm rhy
                    duration dur amplitude amp)))))

See:
	thread, heap, stella.rtf

___________________________________________________________________


MIDI							[Syntax]

The MIDI syntax implements MIDI real time and MIDI score file generation.  Functions and macros related to this syntax are too numerous to include in this document.  See the file doc/midi.rtf for an overview and complete documentation of all midi related functions.

See:
	in-syntax, syntax, midi.rtf

___________________________________________________________________


mirror  stream						[Macro]

mirror produces a period of data from stream followed by its strict retrograde, no matter what patten stream implements.

Example:

<cl> (setf x (mirror (items a b c d in heap)))
#<FUNCTIONAL-ITEM-STREAM 137562641> 

<cl> (read-items x 16)
(A D B C C B D A D C B A A B C D)

See:
	retrograde

___________________________________________________________________


motive name					               [Macro]
#@name						     [Read Macro]

motive and the read macro #@ return the item stream referenced by name. The item stream must have been created using the named constructor option.

Example:

<cl> (setf x (items moe larry curley named stooges))
#<CYCLIC-ITEM-STREAM 137427651> 

<cl> (setf y (items #@stooges nyuk nyuk nyuk ))
#<CYCLIC-ITEM-STREAM 137433241> 

<cl> (read-items y)
(MOE LARRY CURLEY NYUK NYUK NYUK)    

See:
	items

___________________________________________________________________


MusicKit					[Syntax]

The MusicKit syntax implements score file generation for the Music Kit, a sound synthesis package in Objective C on the NeXT Computer, developed by David Jaffe.

See:
	in-syntax, *syntax*

___________________________________________________________________


name name &optional new	[Function]

name is used in place of symbolic names for algorithms, threads, merges and generators defined inside loop constructs.  Use name to insure that each object created in the loop will receive a unique name.  If new is nil (the default) the value returned is name, otherwise if new is true (non-nil) then a new name will be generated with name serving as the root of the new symbol.

See:
	stella.rtf

___________________________________________________________________


note  reference &optional scale				[Function]

note returns the symbolic note name of reference in scale.  Reference may be a note (symbolic name), degree (integer scale position) or pitch (floating point frequency).

Examples:

<cl> (note 'a4)
A4

<cl> (note 440.0)
A4

<cl> (note 69)
A4

See:
	degree, degrees, pitch, pitches

___________________________________________________________________


notes  {item}+ {option}*			   [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
	of scale  

Other options may be applicable based on {pattern}.

notes creates a note stream to return the symbolic names of scale degree references in a specified pattern.   Scale degree references may be notes  (symbol),  degrees (integer), pitches (float) or item streams of the same.   A note that does not include an octave number will automatically be placed in the last octave specified, or the default octave 4 if no octave has been specified. 

The constructors notes, degrees, pitches, intervals, and steps all implement the constructor options:

of {scale}

Sets the scale of  the stream.   Defaults to *standard-scale*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x (notes (notes c2 d) (notes c3 d)
                    (notes c4 d) in heap))
#<HEAP-NOTE-STREAM 136100641> 

<cl> (read-items x)
(C4 D4 C3 D3 C2 D2) 

See:
	degrees, pitches, scales

___________________________________________________________________


numbers  {option}*			   [Item Stream Constructor]

Other options may be applicable based on {pattern}.
The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  
Options:
in {pattern}
for {integer | stream}
	from {number | stream}  
	to {number | stream}  
	below {number | stream}  
	downto {number | stream}  
	above {number | stream}  
	by {number | stream}  

numbers creates number streams for cyclic or random number generation.  numbers is similar in spirit to Lisp's loop iteration macro, except that it is used in conjunction with item to return the next number, and permits any numeric to be a an item stream of values.

numbers implements the following constructor options:

in {pattern}

Sets the  pattern type of the stream. Currently only cycle and random are implemented.

from {number | stream}

Sets the initial value of the stream, which defaults to 0.

to {number | stream}

Sets the inclusive upper bound of the stream.

below {number | stream}

Sets the exclusive upper bound of the stream. 

downto {number | stream}

Sets the inclusive lower bound of the stream.

above {number | stream}

Sets the exclusive lower bound of the stream.

by {number | stream}

Sets the increment of the stream, which defaults to 1.

Example:

<cl> (setf x (numbers from 1 below (items 5 10)
                      in random))
#<RANDOM-NUMBER-STREAM 136100641> 

<cl> (read-items x)
(1 1 1 2) 

<cl> (read-items x)
(3 8 1 6 4 8 1 8 9) 

 See:
	items

___________________________________________________________________


octave-and-interval reference scale			[Function]

octave-and-interval returns the octave and the interval of reference in scale as multiple values.  Reference may be a note (symbol), pitch (floating) or degree (integer).

Example:

<cl> (octave-and-interval 'a4 *standard-scale*)
5
9

See:
	defscale, note, degree, pitch

___________________________________________________________________


palindrome				 [Item Stream Pattern Type]

The palindrome pattern implements a palindromic pattern in its data.  Elements provided to the pattern are treated as a half period of material;  when the pattern reaches its last element it reverses direction and generates its elements in reverse order.   If the elements in a palindrome pattern are all atomic, a mirror image is formed.  However, elements that are item streams still yield their patterns. palindrome permits the direct repetition of the first and last elements in the pattern to be avoided.

The palindrome pattern implements the following item stream constructor option:

elided {yes | no | first | end  | left | right}

Controls whether the first and last data elements are directly repeated as the pattern reverses direction. If no (the default) the elements are directly repeated. If yes, the elements are not repeated. If left or first the initial element is not repeated.  If right or end the final element is not repeated.

Example:

<cl> (setf x (intervals 0 6 11 from (notes c3 fs5) 
                        in palindrome returning note 
                        elided left))
#<CYCLIC-INTERVAL-NOTE-STREAM 136345471> 

<cl> (read-items x)
(C3 FS3 B3 B3 FS3) 

<cl> (read-items x)
(FS5 C6 F6 F6 C6) 

See:
	accumulation, cycle, function, graph, heap, random, rotation,
	sequence 

___________________________________________________________________


pick seq &key (end (length seq)) (start 0)			[Function]
                          avoid (state *cm-state*)					
pick randomly selects and returns an element from seq, which may be any Lisp sequence.  Start is the starting position in seq from which to pick and defaults to 0.  End the the ending position (exclusive) in seq from which to pick and defaults to the length of the sequence.  If specified, avoid is a element to ignore.  Use avoid to inhibit the direct reselection of an element.  State is the random state to use and defaults to Common Music's random state object.

Examples:

<cl> (pick '(1 2 3 4 :foo))
3

<cl> (pick "Silly boy" :start 6)
#\o

See:
	between, pickl
___________________________________________________________________


pickl &rest data					[Function]

pickl is a simplified version of pick that selects and returns an element from the arguments to the function.

Examples:

<cl> (pickl 1 2 3 4 :foo 5)
3

<cl> (pickl 1 2 3 4 :foo 5)
:FOO

See:
	between, pick
___________________________________________________________________


pitch  reference &optional scale				 [Function]


pitch returns the floating point frequency of reference in scale. Reference may be a note (symbolic name), degree (integer scale position) or pitch ( floating point frequency).

Examples:

<cl> (pitch 'a4)
440.00018

<cl> (pitch 440.0)
440.00018

<cl> (pitch 69)
440.00018


See:
	note, notes, degree, degrees

___________________________________________________________________


pitches  {item}+ {option}*			   [Item Stream Constructor]


Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
	of scale  

Other options may be applicable based on {pattern}.

pitches creates a pitch stream to return the floating point frequencies of scale degree references in a specified pattern.   Scale degree references may be notes  (symbol),  degrees (integer), pitches (float) or item streams of the same. 

The constructors pitches, notes, degrees, intervals, and steps all implement the constructor options:

of {scale}

Sets the scale of  the stream.   Defaults to *standard-scale*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x (pitches c4 d e f in random for 8))
#<RANDOM-PITCH-STREAM 137542751> 

<cl> (read-items x)
(349.2283 349.2283 293.66476 349.2283 349.2283 349.2283 	  349.2283 349.2283) 
 
See:
	notes, degrees, scales

___________________________________________________________________


*post-processing*	[Global Variable]

*post-processing* determines if the Write and Swrite commands "post process" files immediately after writing them.  The exact type of processing performed depends on the syntax and type of file.  If *post-processing* is t, then any processing is automatically invoked.  If the value is :ask, then you are prompted to confirm the processing.  Otherwise, if *post-processing* in nil then no processing occurs.  The default value of *post-processing* is :ask.

___________________________________________________________________


quotify string					           [Function]

quotify return string surrounded by string quotes.  String may be either a symbol or a string.

Example:

<cl> (princ (quotify 'foo))
"FOO"
"\"FOO\""

___________________________________________________________________


random					 [Item Stream Pattern Type]

The random pattern implements a random ordering of its data.  Basic random selection may refined by weighting some elements relative to the others, and by constraining the minimum and maximum number of consecutive times an element may be selected.  By default, each element in the pattern has an equal  probabiliy weight and may be reselected in direct succession any number of times.  To qualify the behavior of an item,  use the long form of item specification:

(item &key (:weight 1) (:min 1) :max)

weight is a number representing item's selection probability relative to the weights of all the other items.  The default weight for each item is 1.  weight may be also be specified as an item stream of numbers, in which case a new weighting factor for the item will be set at the beginning of each new period in the stream.  Min constrains how many direct repetitions of item must be made before a new element might be selected.  Max is a ceiling on how many direct repetitions of an element might be made before a new element must be selected.   weight, min and max may be specifed as either keywords or symbols.

The random pattern implements the following item stream constructor options:

using {random state object}

Sets the random state object of the stream, which default to *cm-state*.


Example:

<cl> (setf x (notes c4 d (e weight 3) f g in random))
#<RANDOM-NOTE-STREAM 140173561> 

<cl> (read-items x 10)
(E4 D4 E4 D4 E4 G4 E4 E4 F4 E4) 


See:
	accumulation, cycle, function, graph, heap, palindrome, rotation,
	sequence

___________________________________________________________________


read-items stream &optional length states			[Function]

read-items reads length number of items from stream and returns the results in a list.  If length is t it defaults to the current period length of stream. if states is t then read-items also returns the item stream states.

Example:

<cl> (setf x (items 1 2 3 4 5))
#<CYCLIC-ITEM-STREAM 130412531> 

<cl> (read-items x)
(1 2 3 4 5) 

<cl> (read-items x 10)
(1 2 3 4 5 1 2 3 4 5) 

See:
	item

___________________________________________________________________


repeat stream times			         		  [Macro]

repeat repeats the current period of stream 0 or more  times.   times may be a constant value, an  item stream or an expr.  times is reread each new period of stream.

Example:

<cl> (setf x (repeat (items 1 2 3 in random) 1))
#<FUNCTIONAL-ITEM-STREAM 131611641> 

<cl> (read-items x)
(2 3 1) 

<cl> (read-items x)
(2 3 1) 

<cl> (read-items x)
(1 1 3) 

<cl> (read-items x)
(1 1 3) 

See:
	mirror

___________________________________________________________________


*respect-note-spelling* 				[Variable]

*respect-note-spelling* determines if notes should preserve the spelling of note names as it parses them.   The default value for *respect-note-spelling* is nil, which allows faster parsing and retains the original behavior of notes.  However, if  Common Music is built with CMN then the default value of *respect-note-spelling* is t, under the assumption  that note names should be manuscripted exactly as specified in the data. 

___________________________________________________________________


retrograde  stream						[Macro]

retrograde produces each period of stream in its strict retrograde form, no matter what patten stream implements.

Example:

<cl> (setf x (retrograde (steps 1 2 in random for 8
                                from 'c4 returning note)))
#<FUNCTIONAL-ITEM-STREAM 131442261> 

<cl> (read-items x)
(GS4 G4 FS4 F4 DS4 D4 CS4 C4) 

<cl> (read-items x)
(C5 AS4 GS4 FS4 E4 D4 CS4 C4) 

<cl> (read-items x)
(AS4 A4 G4 F4 E4 DS4 CS4 C4) 

See:
	mirror


___________________________________________________________________


rhythm  reference &optional tempo			[Function]

The rhythm function returns the floating point rhythmic value of a specified rhythm.  The rhythm may be expressed as a rhythmic symbol or as the number of equal divisions of a whole note the rhythmic value occupies.

Examples:

<cl> (rhythm 'w)
4.0 

<cl> (rhythm 'q 90)
0.6666667 

<cl> (rhythm 48 120)
0.041666668 

See:
	rhythms, *standard-tempo*

___________________________________________________________________


rhythms  {item}+ {option}*			   [Item Stream Constructor]


Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
	tempo tempo
	
Other options may be applicable based on {pattern}.


rhythms creates a rhythm stream to returns the floating point value of rhythmic references in a specified pattern.   A rhythmic reference consists of a "base rhythm" that may be optionally qualified for triplet and dotted notations.  A base rhythm is a symbol: D, L, W, H, Q, E, S,  or the number of divisions of a whole note that the rhythm takes up, as in 4, 8, 48, .5, 17, 64, etc.  Numbers may also be expressed in their ordinal form  as in  4th, 8th, 32nd, and so on.  A base rhythm of either type made be made "triplet" by preceding it with a T, is in TQ or T32 and so on.   A rhythm of any type may be optionally dotted as well, as in Q. or T32... and so on. Here is a table showing some basic rhythm notations.

Rhythm		Base Notations
	
Double		D	.25	---
Long		L	.5	---
Whole		W	1	1st
Half		H	2	2nd
Quarter		Q	4	4th
5:4		--	5	5th
Eighth		E	8	8th
10:8		--	10	10th
Sixteenth		S	16	16th
32nd		--	32	32nd	
64th		--	64	64th

Rhythms that cannot be notated by a single token may be written as rhythmic expressions using the infix operators +, -,*,/ as in W+E., Q-T64, etc. No space may separate the operators and the operands.  The expression is parsed from left to right without any notion of operator precedence.   Note: the Lisp reader reads a dotted integer like 4. as the integer 4  without the dot.  This means that Common Music cannot parse a number followed by a single dot as a symbolic rhythm because it never sees the single dot.  There are two ways to write a single-dotted numerical rhythm: (1) Use the ordinal form of the number, ie 4th. or 32nd. (2) delimit the token with the | character, as in |4.| or |16.| which forces the reader to interpret  the token as a symbol.  Of course, numbers followed by more than one dot, for example, 16.. or 8..., do not have a special meaning to the reader and will be parsed correctly.

The rhythms constructor macro implements the constructor options:

tempo {number | tempo function}

Sets the tempo of the stream, which defaults to *standard-tempo*.  The value may be either a metronome number or a tempo envelope.  See documentation on tempo for further details.
	
The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x (rhythms q 16 32.. w+e tempo 90))
#<CYCLIC-RHYTHM-STREAM 137413001> 

<cl> (read-items x)
(0.6666667 0.16666667 0.14583334 3.0) 

See:
	rhythm, in-tempo

___________________________________________________________________


rotation					 [Item Stream Pattern Type]

The rotation pattern rotates its data according to an optional change value controlling up to four independent rotational characteristics: the starting index (zero based) for the rotation in the data, the stepping increment between successive rotations, the width between the elements rotated, and the index in the data to stop rotating at. Each change value is a list of (up to) four numbers:  (&optional (start 0) (step 1) (width 1) (end t)).  The default change causes the first element in the data to continually move to the back.  Multiple changes may be specified as an item stream, or use the changes macro to automatically create one or more changes appropriate to the macro's arguments.
  
The rotation pattern implements the following item stream constructor options:

change {list | stream}

Sets the rotation's change value, which defaults to (0 1 1 t).   The change value is reset once each period.

Examples:

<cl> (setf x (notes a b c d in rotation))
#<ROTATIONAL-NOTE-STREAM 132202211> 

<cl> (loop repeat 4 collect (read-items x))

((A4 B4 C4 D4) (B4 C4 D4 A4) (C4 D4 A4 B4) (D4 A4 B4 C4))

;;
;; Plain Hunt change ringing (thank you, Nicky Hind)
;;

<cl> (setf x 
       (notes a b c d in rotation 
              change (changes start '(0 1) step 2)))
#<ROTATIONAL-NOTE-STREAM 132220261> 

<cl> (loop repeat 8 collect (read-items x))

((A4 B4 C4 D4) (B4 A4 D4 C4) (B4 D4 A4 C4) (D4 B4 C4 A4) (D4 C4 B4 A4) (C4 D4 A4 B4) (C4 A4 D4 B4) (A4 C4 B4 D4)) 

See:
	accumulation, cycle, function, graph, heap, palindrome, random,
	sequence, changes

___________________________________________________________________


RT					 	[Syntax]

The RT syntax produces score files for rt.app, a sound file mixing program written by Paul Lansky at Princeton (paul@washburn.princeton.edu).  RT syntax is only useful on the NeXT computer.

See:
	in-syntax,  syntax, infiles

___________________________________________________________________


scale=  &rest references 				[Function]

scale= returns true if  references all reference the identical scale degree entry.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

Example:

<cl> (scale= 69 'a4 440.0)
T

___________________________________________________________________


scale/=  &rest references 				[Function]

scale/= function returns true if references all reference different scale entries.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

___________________________________________________________________


scale< &rest  references					[Function]

The scale< function returns true if references are all in monotonically decreasing order.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

Example:

<cl> (scale< 'a2 59 440.0)
T

___________________________________________________________________


scale<= &rest  references					[Function]

The scale<= function returns true if the scale references are in monotonically less than or equal order.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

___________________________________________________________________


scale>  &rest references					[Function]
              
The scale> function returns true if references are all in monotonically increasing order.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

Example:

<cl> (scale> 'c6 'a5 440.0)
T

___________________________________________________________________


scale>=  &rest references					[Function]
              
The scale>= function returns true if references are all in monotonically increasing or equal order.  References may be specified as a mixture of notes (symbol), degrees (integer) and pitches (float).

___________________________________________________________________



sequence				 [Item Stream Pattern Type]

The sequence pattern type implements a linear ordering of its data.  Elements are selected in sequential order;  once the last element has been reached it is continually reselected by the pattern. 
    
Example:

<cl> (setf x (items a b c d e in sequence))
#<SEQUENTIAL-ITEM-STREAM 136377321> 

<cl> (read-items x 10)
(A B C D E E E E E E) 

See:
	accumulation, cycle, function, graph, heap, palindrome, random,  
	rotation

___________________________________________________________________


series  {interval}+ {option}*		[Item Stream Constructor]

Other options may be applicable based on {pattern}.
The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  
Options:
	in {pattern}
	for {integer | stream}
	counting {periods | values}
	traversing {depth | breadth}
	named {name}
	of {scale}
	from {scale degree reference | stream}
	on {scale degree reference | stream}
	initially-from {scale degree reference}
	linked-to {name}
	returning {note | pitch | degree}
	forming {p | i | r | ri | stream}
	multiple {integer | stream}
	modulus {integer | stream}

Other options may be applicable based on {pattern}.
	
 series creates a subclass of cyclic interval stream that supports serial (twelve tone) manipulation. 
    
The series macro implements the following options:
	
forming {p | i | r | ri | stream}

The forming option allows the specification of a row form for the set.  The value may be a constant row form or else an item stream of row forms. Legal row forms are: prime, inversion, retrograde 	and retrograde-inversion.  For sake of convenience, these forms may be specified by their  initials p, i, r, ri, or their full-word equivalents. If forming is not specified, the default row form p is used.  The row form is reselected at the beginning of every cycle through the data.  The value of the forming is always evaluated.
	
multiple {integer | stream}

The multiple option allows multiplicative operations to be performed on the set.  The value of the option should either be an interval or an item stream of intervals.  If multiple is not supplied, the default value 1 is used, which means that no transformations can occur.  Its value reselected at the beginning of every cycle through the set. The value of multiple is always evaluated.


modulus {integer | stream}
	
The modulus option allows an interval modulus to be associated with the set. The value of this option should either be an interval or an item stream of intervals.  If modulus is not supplied, no modulus will be associated with the set. If it is specified, the modulus is reselected at the beginning of every cycle through the set. The value of modulus is always evaluated.

For an explanation of the other constructor options available to series, see the documentation topic intervals and items.

Example:

<cl> (setf x (series 0 1 2 3 4 5 6 
                     from (notes a3 a5)
                     forming (items p i r ri)
	               returning note)) 
#<SERIES-NOTE-STREAM 135213471> 

<cl> (read-items x 28)
(A3 AS3 B3 C4 CS4 D4 DS4 A5 GS5 G5 FS5 F5 E5 DS5 DS4 D4 CS4 C4 B3 AS3 A3 DS5 E5 F5 FS5 G5 GS5 A5) 

See:
	intervals

___________________________________________________________________


*standard-scale*				                  [Global Variable]

*standard-scale* provides a default scale object for resolving note references when a scale is not explicitly specified to functions and item streams that require scales.  The initial value for *standard-scale* is a scale object that implements the standard chromatic scale from C00 to B9

See:
	defscale, notes,degrees, pitches, note, degree,
	pitch and in-scale

___________________________________________________________________


*standard-tempo*				                  [Global Variable]

*standard-tempo* provides the default tempo value when a value for tempo is not explicitly specified to functions or item streams that require them.  The initial value of *standard-tempo* is 60. 

See:
	rhythm, rhythms, in-tempo

___________________________________________________________________


status?  status &optional algorithm			[Function]

status?  returns non-nil if status is the current status of algorithm.  status? is like if-status, except that it may be used with any part instance, not just the currently executing part.  The value of status must be one of the following symbols:

:resting

True if the algorithm will not output an event.

:chording

True if the algorithm is currently executing a chord.

:ending

True if the algorithm is done.

:killed

True if the algorithm will not output and is done.

Status values appropriate to all Music Kit algorithms:

:noteOn

True if the algorithm will output a :noteOn.

:noteOff

True if the algorithm will output a :noteOff.

:noteUpdate

True if the algorithm will output a :noteUpdate

___________________________________________________________________


staves  &rest  staff-info					[Macro]

staves  returns a list of CMN staff descriptions based on the staff information supplied in staff-info.  Each entry in staff-info is a list of data giving the overall characteristics for each CMN staff to be drawn:

	(objects &key name clef meter recursive)

Objects are the things that the CMN stream's staffer function should hash on to return the proper CMN staff.  If staffing by container (the default) objects should be the symbolic names of the containers to group in the staff.  Staves internally coerces object names to their corresponding objects.  If staffing by midi channel, objects should be the midi channel numbers (0 to 15)  to group in the staff.  For convenience, objects may be specified as a non-list if there is only one object for the staff.

Name is the print name (string) of the staff.  If name is not supplied it defaults to a  printed representation of objects, if possible, or an auto-generated label if not.

Clef is the clef or clefs that CMN should use when drawing data.  If more than one clef is specified, the first clef is the main clef and the rest are the clefs that CMN is allowed to choose from when positioning the data in the staff.  If clef is :both then the staff data will be drawn in short score (2 staves, treble and bass).   If clef is not supplied, CMN chooses whatever it thinks best.  

Meter is the meter that CMN should use when drawing data.  The default value for meter is nil, which means that by default data will be drawn without meter or barlines.  (If you want to specify a meter that applies to all staves,  it is easiest to initialize the output file's meter slot using the Open command.   See stella.rtf for more information.)

Recursive is a flag for automatically including the sub-containers (if any) of each container specfied in objects.  The default value for recursive is nil, which means that by default sub-containers will be drawn in their own staff.


Examples:

;; midi channel example. All channel 0 data in
;; treble, channel 1 in bass or tenor

(staves (0 :clef treble) (1 :clef (bass tenor)))

;; container example. Foo and Bar in short score 
;; for a piano.

(staves ((foo bar) :clef both :name "Piano"))

See:
	CMN chapter and appendix ??? in tutorial/stella.rtf

___________________________________________________________________


steps  {item}+ {option}*			   [Item Stream Constructor]

Options:
in {pattern}
for {integer | stream}
counting {periods | values}
traversing {depth | breadth}
named {name}
of {scale}
from {scale degree reference | stream}
on {stream}
initially-from {scale degree reference}
linked-to {name}
returning {note | pitch}

Other options may be applicable based on {pattern}.

steps creates a step stream to return integer steps in a specified pattern.  A step describes relative motion in a scale, as opposed to the absolute notes, degrees or pitches of a scale, or the relative distances of intervals.  Each step in the data may be an integer or an item stream that produces integers.  If an optional transposition offset is provided, the values generated by the stream will be transposed to that offset.  The offset may be specified as a note (symbol), pitch (float), degree (integer) or an item steam of the same.  If provided, an offset is reset either once each period or once each read depending on whether it is specified using the from or on options.  steps can be coerced to return either symbolic note names or floating point pitches by using the returning option.

The intervals and steps constructors implement the constructor options:

from {scale degree reference | stream}

Sets the transposition offset of the stream, which defaults to 0.  The transposition offset is reset once each period.  from,  on, initially-from and linked-to are mutually exclusive options.

on  {stream}

Similar to from except that the transposition value is read in parallel with the pattern selection.   from,  on, initially-from and linked-to are mutually exclusive options. 

initially-from {scale degree reference}

Similar to from except that the transposition offset is never reset, so subsequent periods start where the previous ones left left off.  from,  on, initially-from and linked-to are mutually exclusive options.

linked-to {stream name}

Sets the transposition value as the current transposition value of some other stream. The name of the stream is not quoted.   from,  on, initially-from and linked-to are mutually exclusive options.

returning {note | pitch | degree}

Coerces the interval stream to return symbolic note names or floating point frequencies.  

of {scale}

Sets the scale of  the stream.   Defaults to *standard-scale*.

The options in, for, counting, traversing and named apply to all item stream constructors.  See items for more information.  

Example:

<cl> (setf x 
       (steps 1 2 3 in random from 'c4 
                    for 8 returning note))
#<RANDOM-STEP-NOTE-STREAM 130213351> 

<cl> (read-items x 16)
(C4 CS4 D4 DS4 F4 FS4 A4 B4 C4 DS4 E4 F4 G4 A4 AS4 C5) 

See:
	intervals

___________________________________________________________________


*syntaxes*					                	 [Variable]

The global variable *syntaxes* holds the list of syntaxes currently loaded in Common Music.  It should never be reset by the user. 

See:
	in-syntax

___________________________________________________________________


tempo  &rest args					[Macro]
    
tempo creates an appropriate tempo factor for a rhythm stream according to the data provided in args.  There are three forms of tempo specification:

(tempo number &optional (pulse 4))

creates a constant metronome value for the rhythm stream.  Pulse defaults to the quarter note. 

The second form of tempo is a sequence of option value pairs to create either an accelerando or a retardando:

(tempo {option}+)

tempo supports the following options:
	
from {number}

	The initial metronome tempo.

to {number}

	The final metronome tempo.

in {integer}

	The number of pulses the move occupies	

pulse {rhythm}

	The rhythmic value of the pulse, which defaults to a quarter note (4)

update {before | after}

Controls whether the tempo changes occur on each rhythm or between each rhythm.  If  :before (the default)  the change occurs on each rhythm.  If :after, the change occurs between each rhythm

The final form of tempo specification is as a list of function coordinates that are followed by zero or more options:
	
(tempo {coordinate pair}+ {option}*)

The x coordinates range from 0 to the number of beats the tempo change spans, and the y coordinates are metronome  tempi.  Legal options are pulse and update, which were described in the preceding paragraph.

Examples:

<cl> (setf x (rhythms q for 8 tempo (tempo 60)))
#<CYCLIC-RHYTHM-STREAM 131654651> 

<cl> (read-items x)
(1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0) 

<cl> (setf x
       (rhythms q for 8 
          tempo (tempo from 60 to 120 in 8)))
#<CYCLIC-RHYTHM-STREAM 131754301> 

<cl> (read-items x)
(0.9375 0.875 0.8125 0.75 0.6875 0.625 0.5625 0.5) 
 
<cl> (setf x
       (rhythms q for 8 
          tempo (tempo 0 60 6 90 8 120)))
#<CYCLIC-RHYTHM-STREAM 132223341> 

<cl> (read-items x)
(0.9444444 0.8888889 0.8333334 0.7777778 0.7222222 
           0.6666667 0.5833334 0.5)

See:
	functions

___________________________________________________________________


thread name options &body body				[Macro]
    
thread creates redefines a thread object.  A thread is a type of collection  that arranges and access its subobjects in sequential order.  name is the name for the new thread.  options is a list of zero or more slot initializations in the form of slot and value pairs.  Currently, the only initialization you should supply for a thread is start.  If start is specified it becomes the permanent start time (until you change it) for the new thread.  Following the options list comes the body of the Thread definition.  Any lisp code is legal here.  Normally, this code would create other elements or containers.  Objects created inside the body of the Thread definition will automatically be added as elements to the thread in the order they are created.  

Example:

(thread test ()
  (doitems (x (notes c4 d ef f g in random for 10))
    (element midi-note note x rhythm .1)))

See:
	merge, heap, stella.rtf

___________________________________________________________________


transpose reference interval &optional scale			[Function]

transpose transposes reference by interval amount.  Reference may be a note (symbol), degree (integer), or pitch (float).  Scale is the scale to transpose reference in, and defaults to *standard-scale*.   transpose returns the same type of reference as reference.

Examples:

<cl> (transpose 'a4 1)
AS4 

<cl> (transpose 69 1)
70 

<cl> (transpose 440.0 1)
466.16397 

See:
	cm/doc/scales.rtf

___________________________________________________________________


unless-chording  &body body				[Macro]

unless-chording insures that forms in its body are not evaluated if an algorithm is currently in the process of generating a chord.  This avoids the necessity of "padding" item streams with items just to remain in parallel with a note stream that is generating chord members.  For example, the duration and amplitude of a algorithm normally remain the same for all members of a chord.  By wrapping these forms inside unless-chording, only one amplitude and one duration value need be specified for the entire chord.

Example:

(algorithm foo fm1vi ()
  (setf freq (item (notes [c4 ef g] [d f a] [e g b])
                   :kill t))
  (unless-chording
    (setf rhythm (item (rhythms q s e))
          amp (item (items .1 .2 .3))))))

See:
	scales

___________________________________________________________________


unless-resting  &body body					[Macro]

unless-resting insures that forms in its body are not evaluated if the algorithm is currently in the process of resting.  This avoids the necessity of "padding" item streams with items just to remain in parallel with a note stream that is generating rests.  For example, the amplitude of an algorithm is irrelevant when the algorithm is resting. By wrapping its form  inside  unless-resting, an amplitude value need be specified for the rest.

Example:

(algorithm foo fm1vi (rhythm .25)
  (setf freq (item (notes c4 r d r e)
                   :kill 2))
  (unless-resting
    (setf amp (item (items .1 .2 .3))))))

See:
	scales

___________________________________________________________________


vars &rest bindings		[Algorithm Special Form]


The vars declaration may appear as the first form in the body of an algorithm or generator to declare local variables that are to be reinitialized each time the object is scheduled to begin its output processing.   The syntax of a vars declaration is similar to Lisp's let* declaration binding list: each form in a vars declaration can be either the name of a variable, or a binding list (name value), where value is the initial value of the variable.  Variables in the vars statement are processed in sequential order, so a variable binding can reference a previous variable's value.  For example,

	(vars a (b 2) (c (* b 3)))

would declare 3 locals variables: a b and c. Each time the algorithm is scheduled to begin running, a will be initialized to nil, b to 2, and c to 6.

See:
	algorithm, generator, stella.rtf

___________________________________________________________________


*warn-if-redefine-object* 	              				 [Variable]

*warn-if-redefine-object* controls whether or not a warning is given if an object is redefined.   The default value is t.

___________________________________________________________________


when-chording  &body body				[Macro]

 when-chording macro insures that forms in its body are evaluated only if the algorithm is currently in the process of generating a chord. 

See:
	unless-chording, status?

___________________________________________________________________


when-resting  &body body					[Macro]

when-resting macro insures that forms in its body are evaluated only if the algorithm is currently in the process of resting.

See:
	unless-resting, status?
	

These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.