Main Page       Index


orff.lsp


 orff.lsp
 Version 1.03  27 May 2005, Reworked stack hungry :out method.
 Version 1.02  26 May 2005, Added documentation.
 Version 1.01  26 May 2005, Incremental changes.
 Version 1.00  25 May 2005, Initial lisp code.
 Versions prior to 1.00 implemented in python.

 Author Steven Jones

 Contact jones57@swbell.net include the word "nyquist" in subject line

 The contents of this file are released under the terms of the GNU General
 Public License. See the file LICENSE.txt

 ORFF is an algorithmic composition package based loosely on the Carl Orff
 method of music education. The basic procedure is as follows. The composer
 provides a rhythmic cue-list, a list of possible pitches and an orchestra
 of instruments. The algorithm then selects for each instrument a
 sub-sequence from the cue list. For each sub-sequence event a random
 note is selected from the note list. There are a few options in the
 selection process which allow for tone rows etc. Orff does not directly
 produce sound. Instead the output is a Nyquist program in text form. You
 evaluate this program to actually generate audio output. The decision to
 output to text was two-fold. First it provides a record of the results,
 secondly text is easily alterable.


class

orff:part

 The orff:part class is responsible for selecting sub-sequences from a
 cue-list. Pitch values are randomly assigned to each event in the
 sub-sequence and a list of "gate" or note durations is generated.
 The :out method is used to generate code for a single Nyquist function to 
 "play"the part.


method

orff:part :new

 (send orff:part :new  cset n [:pset][:u][:c][:cmode][:pmode])
 Construct new orff:part object.

 cset   - List. The master cue-list should be a list of the form 
          (t0 t1 t2 ... tn) where ti is the time for event i. The time 
          unit defaults to 1/16th notes but may be changed via the :u 
          argument.

 n      - Integer. The number of events to "pull" out of cset.

 :pset  - List. List of possible pitch classes. Both individual notes and 
          list of notes (for chords) are allowed. 
          Default orff:*default-pset*, a pentatonic scale in c.
 
 :u     - Flonum | Symbol. Sets the basic time unit. 
          See tempo.lsp for details. 
          Default 's  (1/16th note)

 :c     - Integer. Sets the length of the cue-list in basic time units. 
          The c, for "count", value is used to calculate offset times for 
          phrase repetitions. Typically it is set to the length of the 
          cue-list phrase but other values are possible. If c is less then 
          the cue list length, some phrase overlapping will occur. 
          Conversely if c is too large gaps will appear between phrase 
          repetitions. Default 16.

 :cmode - Symbol. Determines method for selection of cue-list events.
          There are three possibilities: 'SEQ 'RND 'ROW
          The default is SEQ.

          'SEQ - Cue list events are selected in sequence. That is a 
                 strict sub-sequence of cset is used. 

          'RND - Events are pulled from cset at random with possible 
                 duplications. If duplications occur multiple notes 
                 will play simultaneously. 
          
          'ROW - Events are pulled from cset at random, duplications are 
                 not allowed. In practice this means that notes will never 
                 occur simultaneously. Note however that if n is greater 
                 then the length of cset, then there is no choice but to 
                 allow some duplications.

 :pmode - Symbol. Determine method for selection of pitch values from pset.
          The possible modes are the same as for cmode: 'SEQ 'RND 'ROW
          The default is RND.

 return - Object. A new instance of ORFF:PART


method

orff:part clone

 (send /orff:part/ :clone)

 Return - Object. A new instance of orff:part with the same cue list and 
 notelist as this object. 


method

orff:part :unit

 (send /orff:part/ :unit)
 
 return - Symbol | Flonum. the basic time unit.


method

orff:part :count

 (send /orff:part/ :count)
 
 return - flonum. The basic time unit count.


method

orff:part :length

 (send /orff:part/ :length)
 
 return - Integer. The number of cue-list events.


method

orff:part :cuelist

 (send /orff:part/ :cuelist [val])
 Return and optionally change the cue list 
 
 val    - List. The new cue-list. If nil the instance cue list is unchanged. 
          Default nil.
 return - List.


method

orff:part :notelist

 (send /orff:part/ :notelist [val])
 Return and optionally change the note list.

 val    - List. The new note-list. If nil the current note list is 
          unchanged. Default nil
 return - list.


method

orff:part :gatelist

 (send /orff:part/ :gatelist [val])
 Return and optionally set gatelist.
 
 val    - List. The new gate list. If nil the current gate list is 
          unchanged. Default nil
 return - list.


method

orff:part :transpose

 (send /orff:part/ :transpose n)
 Transpose note list elements by n half-steps. 
 Note nested list within notelist are also transposed.
 
 n - integer.



method

orff:part :retrograde

 (send /orff:part/ :retrograde [:pitch][:cue])
 Replace cue and/or note list with their retrogrades.

 :pitch - Boolean. If true reverse note-list. Default t
 :cue   - Boolean. If true reverse the cue list. Default t


method

orff:part :rep

 (send /orff:part/ :rep  [echo])
 Produce string representation of this instance.
 
 echo   - Boolean. If true dump results to standard out.
          Default t

 return - String | nil. If echo is false the string representation is 
          returned.


method

orff:part :out

 (send /orff:part/ :out target fn [:pflag][:gflag])
 Generate Nyquist function to play this part. The new function is in the
 form of a string which needs to be evaluated by Nyquist prior to its use.

 target - String. The name for the new function

 fn     - String. The name of the instrument function used to actually 
          produce sound. fn should take 0, 1 or 2 arguments and return 
          sound. 

 :pflag - Boolean. Set to true if fn expects a pitch as its first argument. 
          Default t.

 :gflag - Boolean. Set to true if fn expects a duration as its only or 
          second argument. Default t

 return - String. The new functions definition as text.


class

ORFF

 The ORFF class utilizes a series of orff:part instances to generate a
 Nyquist program.


method

orff :new

 (send orff :new  clist [:u][:c][:pset])
 Create new instance of orff class. Initially the instance contains no
 "parts", use the :add method to specify an "orchestra".

 clist  - List. The master cue-list provides the overall rhythmic pattern. 
          The list should have the form (t0 t1 t2...tn) where ti is the 
          time of the ith event in basic time unit.  

 :u     - Symbol | Flonum. Sets the basic time unit. See tempo.lsp for 
          details, default 's 

 :c     - Integer. Count of basic time units in clist. Together with :u, 
          :c sets the primary time-signature. Default 16.

 :pset  - List. The default pitch class which may be overridden by the 
          :add method. By default orff:*default-pset* a pentatonic scale 
          in c.

 return - Object. A new instance of ORFF


method

orff :add

 (send /orff/ :add  target fn n [:pset][:pmode][:cmode][:transpose][:pflag][:gflag][:mix])
 Add instrument part to score. 
 
 target     - String. Name of the Nyquist function for the new part.

 fn         - String. Name of the function used to render the part. 
              fn should expect 0, 1 or 2 arguments (see pflag and gflag 
              below) and return sound.

 n          - Integer. The number of events to pull out of the master cue 
              list.

 :pset      - List. Set of possible pitch values, nested list are allowed 
              for chords. Default orff:*default-pset* a pentatonic scale 
              in c.

 :pmode     - Symbol. Pitch selection mode. Possible values are 'SEQ 'RND 
              and 'ROW. See orff:part constructor for details. Default 'RND

 :cmode     - Symbol. Cue list selection method. Possible values are
              'SEQ 'RND and 'ROW. See orff:part constructor for details.
              Default 'SEQ

 :transpose - Integer. A transposition, in half-steps, added to pset. 
              Default 0.

 :pflag     - Boolean. If true a pitch argument is passed to fn as its first 
              argument. If fn does not expect a pitch argument pflag should 
              be false. Default t.

 :gflag     - Boolean. If true a duration or "gate" argument is passed to 
              fn as its first (if pflag is false) or second (if pflag is 
              true) argument. If fn does not expect a duration argument 
              gflag should be false. Default t.

 :mix       - Flonum. Set the relative amplitude of this part in DB.
              Default 0.

 return     - Object. A new instance of ORFF:PART is created and added to 
              the parts list for this instance of ORFF. The new ORFF:PART 
              object serves as the return value for :add. 


method

orff :require

 (send /orff/ :require  sym)
 Used to force load any required LISP files in the final output
 code. Typically the sound generating functions passed to the :add method
 would be required. See require function in utilities.lsp for details

 sym    - Symbol.


method

orff :tempo

 (send /orff/ :tempo  n)
 Add "set-tempo" call to final output code.

 n - flonum. The tempo in BPM.


method

orff :out

 (send /orff/ :out target outfile)
 Produce Nyquist code as text and write it out to a file.

 target  - String. The name of the top-level function within the code.
           Target simply wraps calls to individual part functions 
           within a sim. Optional amplitude scaling is also provided. 

 outfile - String. output file name. File names may be relative to 
           the current directory or absolute. 


example

orff

;; @doc example orff
;; ***************************************************************************  
;;			      Example orff usage
;; ***************************************************************************  

;; The master cue list, a 2-bar phrase, repeated twice.
;; u = 's  c = 64
;;

(setf clst (list  0  3  4  8 11 12
		 16 19 20 24 27 28 30
		 32 35 36 40 43 44
		 48 51 52 56 59 60 61))
		 
		 
;; Possible pitch values, a simple pentatonic scale
;;

(setf nlst (list c3 d3 e3 g3 a3))


;; Create new orff object, initially there are no "parts".
;;

(setf orffobj (send orff :new clst :u 's :c 62 :pset nlst))


;; Make sure required instrument functions are loaded.
;;

(send orffobj :require "marimba")
(send orffobj :require "vibraphone")
(send orffobj :require "fmpiano")


;; Optionally set a temp, easily alterable later 
;;

(send orffobj :tempo 140)


;; Add "parts"
;;

(send orffobj :add "p1" "marimba" 8 :cmode 'RND :transpose 12)
(send orffobj :add "p2" "marimba" 12 :cmode 'SEQ :pmode 'SEQ )
(send orffobj :add "p3" "vibraphone" 5 :cmode 'RND)
(send orffobj :add "p4" "fmpiano" 12 :cmode 'SEQ :pmode 'RND :transpose 24)
(send orffobj :add "p5" "fmpiano" 16 :cmode 'RND :transpose -12)


;; Write the result to the current directory, hopefully this is on your XLISP
;; path.
;;

(send orffobj :out "foo" "orfftest.lsp")


;; The new score now needs to be loaded into Nyquist
;;

(load "orfftest")
(play (foo))


View the Sourcecode :



;; orff.lsp
;; Version 1.03  27 May 2005, Reworked stack hungry :out method.
;; Version 1.02  26 May 2005, Added documentation.
;; Version 1.01  26 May 2005, Incremental changes.
;; Version 1.00  25 May 2005, Initial lisp code.
;; Versions prior to 1.00 implemented in python.
;;
;; Author Steven Jones
;;
;; Contact jones57@swbell.net include the word "nyquist" in subject line
;;
;; The contents of this file are released under the terms of the GNU General
;; Public License. See the file LICENSE.txt
;;
;; ORFF is an algorithmic composition package based loosely on the Carl Orff
;; method of music education. The basic procedure is as follows. The composer
;; provides a rhythmic cue-list, a list of possible pitches and an orchestra
;; of instruments. The algorithm then selects for each instrument a
;; sub-sequence from the cue list. For each sub-sequence event a random
;; note is selected from the note list. There are a few options in the
;; selection process which allow for tone rows etc. Orff does not directly
;; produce sound. Instead the output is a Nyquist program in text form. You
;; evaluate this program to actually generate audio output. The decision to
;; output to text was two-fold. First it provides a record of the results,
;; secondly text is easily alterable.
;;

;(require 'keydict)
(require 'su)
(require 'math)
(provide 'orff)
(current-file "orff")


;; The default pitch class, a pentatonic scale in c.
;;

(setf orff:*default-pset*  (list c3 e3 f3 g3 a3))


; ***************************************************************************  
;			      Utility Functions
; ***************************************************************************  

;; Transpose list of notes, nested list are allowed.
;;

(defun orff:transpose (lst n)
  (cond ((null lst) nil)
	((listp (car lst))
	 (cons (orff:transpose (car lst) n)
	       (orff:transpose (cdr lst) n)))
	((numberp (car lst))
	 (cons (+ (car lst) n)
	       (orff:transpose (cdr lst) n)))
	;((stringp (car lst))
	 ;(cons (keydict:n->str (+ (keydict:str->n (car lst)) n))
	 ;      (orff:transpose (cdr lst) n)))
	(t
	 (error (format nil "ORFF:TRANSPOSE can not transpose ~a" (car lst))))))


;; Convert note list to equivalent list of symbolic strings.
;;
;(defun orff:->symbolic-notelist (lst)
;  (cond ((null lst) nil)
;	((numberp (car lst))
;	 (cons (keydict:n->str (car lst))(orff:->symbolic-notelist (cdr lst))))
;	((stringp (car lst))
;	 (cons (string-upcase (car lst))(orff:->symbolic-notelist (cdr lst))))
;	((listp (car lst))
;	 (cons (orff:->symbolic-notelist (car lst))
;	       (orff:->symbolic-notelist (cdr lst))))
;		
;	(t
;	 (error "Should never see this"))))


;; Select n-length sub-sequence from src
;; src    - list
;; n      - integer
;; return - list
;;

(defun orff:select-sequence (src n)
  (let (max-start start rs)
    (setf n (max 1 (min n (length src))))
    (setf max-start (- (length src) n))
    (setf start (truncate (rndr 0 max-start)))
    (setf rs '())
    (dotimes (i n)
      (push (nth (+ start i) src) rs))
    (reverse rs)))


;; Select n elements at random from src, duplicates are allowed.
;; src    - list
;; n      - integer
;; return - list
;;

(defun orff:select-with-duplicates (src n)
  (let ((rs '()))
    (dotimes (i n)
      (push (pick src) rs))
    rs))


;; Select n elements at random from src without duplications.
;; A problem arises if n is greater then length of src, there must be 
;; duplicates. The solution is to break the result into n-element 
;; sections, no duplicates are allowed within any section.
;;
;; src    - list
;; n      - integer
;; return - list
;;
;; ISSUE: Code a bit ugly here!
;;

(defun orff:select-no-duplicates (src n)
  (if (<= n (length src))
      (let (temp rs)
	(setf temp (permute src))
	(setf rs '())
	(dotimes (i n)
	  (push (nth i temp) rs))
	rs)
    (append (orff:select-no-duplicates src (length src))
	    (orff:select-no-duplicates src (- n (length src))))))


;; Reverse note list order
;;

(setfn orff:note-list-retrograde reverse)


;; Reverse cue-list order
;; clst   - list.
;; count  - Flonum.
;; return - list
;; For each e in clst, 0 <= e < count  ---> e' = count - e
;; 

(defun orff:cue-list-retrograde (clst count)
  (let (rs)
    (setf rs '())
    (dolist (q clst)
      (push (- count q) rs))
    rs))


;; Generate list of note durations given cue-list.
;; Whenever a duration can not be determined without scanning clst forward by
;; more then 1 event, the default duration is used. The final duration is the
;; mean of the other durations.
;;
;; clst    - list
;; default - flonum. The default "on" time
;; return  - list
;;

(defun orff:diff-list (clst &optional (default q))
  (let (rs diff)
    (setf rs '())
    (dotimes (i (length (cdr clst)))
      (setf diff (- (nth (+ i 1) clst)(nth i clst)))
      (if (not (plusp diff))
	  (setf diff default))
      (push diff rs))
    (push (apply #'mean rs) rs)
    (reverse rs)))


; ***************************************************************************
;			       ORFF:PART class
; ***************************************************************************  

;; @doc class orff:part
;; The orff:part class is responsible for selecting sub-sequences from a
;; cue-list. Pitch values are randomly assigned to each event in the
;; sub-sequence and a list of "gate" or note durations is generated.
;; The :out method is used to generate code for a single Nyquist function to 
;; "play"the part.

(setf orff:part (send class :new '(unit count cuelist gatelist notelist)))


;; @doc method orff:part :new
;; (send orff:part :new  cset n [:pset][:u][:c][:cmode][:pmode])
;; Construct new orff:part object.
;;
;; cset   - List. The master cue-list should be a list of the form 
;;          (t0 t1 t2 ... tn) where ti is the time for event i. The time 
;;          unit defaults to 1/16th notes but may be changed via the :u 
;;          argument.
;;
;; n      - Integer. The number of events to "pull" out of cset.
;;
;; :pset  - List. List of possible pitch classes. Both individual notes and 
;;          list of notes (for chords) are allowed. 
;;          Default orff:*default-pset*, a pentatonic scale in c.
;; 
;; :u     - Flonum | Symbol. Sets the basic time unit. 
;;          See tempo.lsp for details. 
;;          Default 's  (1/16th note)
;;
;; :c     - Integer. Sets the length of the cue-list in basic time units. 
;;          The c, for "count", value is used to calculate offset times for 
;;          phrase repetitions. Typically it is set to the length of the 
;;          cue-list phrase but other values are possible. If c is less then 
;;          the cue list length, some phrase overlapping will occur. 
;;          Conversely if c is too large gaps will appear between phrase 
;;          repetitions. Default 16.
;;
;; :cmode - Symbol. Determines method for selection of cue-list events.
;;          There are three possibilities: 'SEQ 'RND 'ROW
;;          The default is SEQ.
;;
;;          'SEQ - Cue list events are selected in sequence. That is a 
;;                 strict sub-sequence of cset is used. 
;;
;;          'RND - Events are pulled from cset at random with possible 
;;                 duplications. If duplications occur multiple notes 
;;                 will play simultaneously. 
;;          
;;          'ROW - Events are pulled from cset at random, duplications are 
;;                 not allowed. In practice this means that notes will never 
;;                 occur simultaneously. Note however that if n is greater 
;;                 then the length of cset, then there is no choice but to 
;;                 allow some duplications.
;;
;; :pmode - Symbol. Determine method for selection of pitch values from pset.
;;          The possible modes are the same as for cmode: 'SEQ 'RND 'ROW
;;          The default is RND.
;;
;; return - Object. A new instance of ORFF:PART
;;

(send orff:part :answer :isnew '(cset n  &key pset u c cmode pmode)
      '((setf pset (or pset orff:*default-pset*))
	(setf unit (or u 's))
	(setf count (or c 16))
	(setf pmode (or pmode 'RND)) 
	(setf cmode (or cmode 'SEQ))
	
	(setf cuelist (cond ((eq cmode 'RND)
			     (orff:select-with-duplicates cset n))
			    ((eq cmode 'ROW)
			     (orff:select-no-duplicates cset n))
			    (t (orff:select-sequence cset n))))

	(setf cuelist (sort cuelist #'<))

	(setf gatelist (orff:diff-list cuelist))

	(setf notelist (cond ((eq pmode 'RND)
			      (orff:select-with-duplicates pset n))
			     ((eq pmode 'ROW)
			      (orff:select-no-duplicates pset n))
			     (t (orff:select-sequence pset n))))
	))


;; Private method used to explicitly set instance fields as part of cloning.
;;

(send orff:part :answer :-set '(u c clst nlst)
      '((setf unit u
	      count c
	      cuelist clst
	      notelist nlst)))


;; @doc method orff:part clone
;; (send /orff:part/ :clone)
;;
;; Return - Object. A new instance of orff:part with the same cue list and 
;; notelist as this object. 
;;

(send orff:part :answer :clone '()
      '((let (obj)
	  (setf obj (send orff:part :new '(1) 0))
	  (send obj :-set unit count cuelist notelist)
	  obj)))


;; @doc method orff:part :unit
;; (send /orff:part/ :unit)
;; 
;; return - Symbol | Flonum. the basic time unit.
;;

(send orff:part :answer :unit '() '(unit))


;; @doc method orff:part :count
;; (send /orff:part/ :count)
;; 
;; return - flonum. The basic time unit count.
;;

(send orff:part :answer :count '() '(count))


;; @doc method orff:part :length
;; (send /orff:part/ :length)
;; 
;; return - Integer. The number of cue-list events.
;;

(send orff:part :answer :length '() '((length cuelist)))


;; @doc method orff:part :cuelist
;; (send /orff:part/ :cuelist [val])
;; Return and optionally change the cue list 
;; 
;; val    - List. The new cue-list. If nil the instance cue list is unchanged. 
;;          Default nil.
;; return - List.
;;

(send orff:part :answer :cuelist '(&optional val) 
      '((if val
	    (setf cuelist val))
	cuelist))


;; @doc method orff:part :notelist
;; (send /orff:part/ :notelist [val])
;; Return and optionally change the note list.
;;
;; val    - List. The new note-list. If nil the current note list is 
;;          unchanged. Default nil
;; return - list.
;;

(send orff:part :answer :notelist '(&optional val) 
      '((if val
	    (setf notelist val))
	notelist))


;; @doc method orff:part :gatelist
;; (send /orff:part/ :gatelist [val])
;; Return and optionally set gatelist.
;; 
;; val    - List. The new gate list. If nil the current gate list is 
;;          unchanged. Default nil
;; return - list.
;;

(send orff:part :answer :gatelist '(&optional val)
      '((if val
	    (setf gatelist val))
	gatelist))


;; @doc method orff:part :transpose
;; (send /orff:part/ :transpose n)
;; Transpose note list elements by n half-steps. 
;; Note nested list within notelist are also transposed.
;; 
;; n - integer.
;;

(send orff:part :answer :transpose '(n)
      '((setf notelist (orff:transpose notelist n))))


;; @doc method orff:part :retrograde
;; (send /orff:part/ :retrograde [:pitch][:cue])
;; Replace cue and/or note list with their retrogrades.
;;
;; :pitch - Boolean. If true reverse note-list. Default t
;; :cue   - Boolean. If true reverse the cue list. Default t
;;

(send orff:part :answer :retrograde '(&key (pitch t)(cue t))
      '((if pitch
	    (setf notelist (orff:note-list-retrograde notelist)))
	(if cue
	    (setf cuelist (orff:cue-list-retrograde cuelist count)))))


;; @doc method orff:part :rep
;; (send /orff:part/ :rep  [echo])
;; Produce string representation of this instance.
;; 
;; echo   - Boolean. If true dump results to standard out.
;;          Default t
;;
;; return - String | nil. If echo is false the string representation is 
;;          returned.
;;

(send orff:part :answer :rep '(&optional (echo t))
      '((let ((acc ""))
	  (setf acc (format nil   ";; ORFF:PART~%"))
	  (setf acc (format nil "~a;;    count ~a   unit ~a~%" acc count unit))
	  (setf acc (format nil "~a;;    cuelist  ~a~%" acc cuelist))
	  (setf acc (format nil "~a;;    notelist ~a~%" acc notelist))
	  (setf acc (format nil "~a;;    gatelist ~a~%" acc gatelist))
	  (format echo "~a" acc))))


;; macro used to concatenate strings
;; sym   - symbol
;; frmt  - Format string, as used by format
;; args  - Arbitrary values as needed by format strings.
;;
;; the result is placed in sym 
;; sym <-- sym + format(....)
;;

(defmacro orff:cat (sym frmt &rest args)
  `(setf ,sym (format nil (strcat "~a" ,frmt) ,sym ,@args)))


;; @doc method orff:part :out
;; (send /orff:part/ :out target fn [:pflag][:gflag])
;; Generate Nyquist function to play this part. The new function is in the
;; form of a string which needs to be evaluated by Nyquist prior to its use.
;;
;; target - String. The name for the new function
;;
;; fn     - String. The name of the instrument function used to actually 
;;          produce sound. fn should take 0, 1 or 2 arguments and return 
;;          sound. 
;;
;; :pflag - Boolean. Set to true if fn expects a pitch as its first argument. 
;;          Default t.
;;
;; :gflag - Boolean. Set to true if fn expects a duration as its only or 
;;          second argument. Default t
;;
;; return - String. The new functions definition as text.
;;

(send orff:part :answer :out '(target fn &key (pflag 't)(gflag 't))
      '((let (head body)
	  (setf head (format nil "(defun ~a (&optional (reps 1))~%" target))
	  (setf body (format nil "   (let (btu plen start)~%"))
	  (orff:cat body
		    "     (setf btu (get-time-symbol-value ~a))~%" unit)
	  (orff:cat body 
		    "     (setf plen (* ~a btu ))~%" count)

	  (orff:cat body
		    "     (sim (at 0 (cue (scale 0 (~a " fn)
	  (if pflag (orff:cat body " 60"))
	  (if gflag (orff:cat body " 1"))
	  (orff:cat body "))))~%")
		
	  (orff:cat body "        (simrep (r (truncate reps))~%")
	  (orff:cat body "           (progn~%")
	  (orff:cat body "              (setf start (* r plen))~%")
	  (orff:cat body "              (sim~%")
	  (dotimes (i (length cuelist))
	    (orff:cat body "              (at (+ start (* ~a btu))(cue (~a " 
		      (nth i cuelist) fn)
	    ;(if pflag (orff:cat body " ~a" (nth i notelist)
	    (if pflag (let ((nt (nth i notelist)))
			(if (listp nt)
			    (progn 
			      (orff:cat body " (list ")
			      (dolist (i nt)
				(orff:cat body " ~a" i))
			      (orff:cat body ")"))
			  (orff:cat body " ~a" nt))))

	    (if gflag (orff:cat body " (* ~a btu)" (nth i gatelist)))
	    (orff:cat body ")))~%"))
	  (orff:cat body "  ))))))~%")
	  (strcat head body ))))


; ***************************************************************************  
;				  ORFF class
; ***************************************************************************  

;; @doc class ORFF
;; The ORFF class utilizes a series of orff:part instances to generate a
;; Nyquist program.
;;

(setf orff (send class :new '(cuelist count unit notelist reqlist tempo parts )))


;; @doc method orff :new
;; (send orff :new  clist [:u][:c][:pset])
;; Create new instance of orff class. Initially the instance contains no
;; "parts", use the :add method to specify an "orchestra".
;;
;; clist  - List. The master cue-list provides the overall rhythmic pattern. 
;;          The list should have the form (t0 t1 t2...tn) where ti is the 
;;          time of the ith event in basic time unit.  
;;
;; :u     - Symbol | Flonum. Sets the basic time unit. See tempo.lsp for 
;;          details, default 's 
;;
;; :c     - Integer. Count of basic time units in clist. Together with :u, 
;;          :c sets the primary time-signature. Default 16.
;;
;; :pset  - List. The default pitch class which may be overridden by the 
;;          :add method. By default orff:*default-pset* a pentatonic scale 
;;          in c.
;;
;; return - Object. A new instance of ORFF
;;

(send orff :answer :isnew '(clist &key u c pset)
      '((setf cuelist clist)
	(setf count (or c 16))
	(setf unit (or u 's))
	(setf notelist (or pset orff:*default-pset*))
	(setf reqlist '())
	(setf tempo nil)
	(setf parts '())))


;; @doc method orff :add
;; (send /orff/ :add  target fn n [:pset][:pmode][:cmode][:transpose][:pflag][:gflag][:mix])
;; Add instrument part to score. 
;; 
;; target     - String. Name of the Nyquist function for the new part.
;;
;; fn         - String. Name of the function used to render the part. 
;;              fn should expect 0, 1 or 2 arguments (see pflag and gflag 
;;              below) and return sound.
;;
;; n          - Integer. The number of events to pull out of the master cue 
;;              list.
;;
;; :pset      - List. Set of possible pitch values, nested list are allowed 
;;              for chords. Default orff:*default-pset* a pentatonic scale 
;;              in c.
;;
;; :pmode     - Symbol. Pitch selection mode. Possible values are 'SEQ 'RND 
;;              and 'ROW. See orff:part constructor for details. Default 'RND
;;
;; :cmode     - Symbol. Cue list selection method. Possible values are
;;              'SEQ 'RND and 'ROW. See orff:part constructor for details.
;;              Default 'SEQ
;;
;; :transpose - Integer. A transposition, in half-steps, added to pset. 
;;              Default 0.
;;
;; :pflag     - Boolean. If true a pitch argument is passed to fn as its first 
;;              argument. If fn does not expect a pitch argument pflag should 
;;              be false. Default t.
;;
;; :gflag     - Boolean. If true a duration or "gate" argument is passed to 
;;              fn as its first (if pflag is false) or second (if pflag is 
;;              true) argument. If fn does not expect a duration argument 
;;              gflag should be false. Default t.
;;
;; :mix       - Flonum. Set the relative amplitude of this part in DB.
;;              Default 0.
;;
;; return     - Object. A new instance of ORFF:PART is created and added to 
;;              the parts list for this instance of ORFF. The new ORFF:PART 
;;              object serves as the return value for :add. 
;;

(send orff :answer :add '(target fn n &key pset pmode cmode transpose (pflag t)(gflag t)(mix 0))
      '((let (partobj)
	  (setf partobj (send orff:part :new 
			      cuelist n 
			      :pset (or pset notelist)
			      :u unit
			      :c count
			      :cmode cmode
			      :pmode pmode))
	  (send partobj :transpose (or transpose 0))
	  (push (list target fn partobj pflag gflag mix)  parts)
	  partobj)))


;; @doc method orff :require
;; (send /orff/ :require  sym)
;; Used to force load any required LISP files in the final output
;; code. Typically the sound generating functions passed to the :add method
;; would be required. See require function in utilities.lsp for details
;;
;; sym    - Symbol.
;;

(send orff :answer :require '(sym)
      '((if (not (member sym reqlist :test #'eq))
	    (push sym reqlist))))


;; @doc method orff :tempo
;; (send /orff/ :tempo  n)
;; Add "set-tempo" call to final output code.
;;
;; n - flonum. The tempo in BPM.
;;

(send orff :answer :tempo '(val)
      '((setf tempo val)))


;; private macro used by :out to format text and output to 
;; file-object fobj.
;;

(defmacro orff:pline (frmt &rest args)
  `(progn 
     (princ (apply #'format (append (list nil ,frmt)(list ,@args))) fobj)
     (terpri fobj)))


;; @doc method orff :out
;; (send /orff/ :out target outfile)
;; Produce Nyquist code as text and write it out to a file.
;;
;; target  - String. The name of the top-level function within the code.
;;           Target simply wraps calls to individual part functions 
;;           within a sim. Optional amplitude scaling is also provided. 
;;
;; outfile - String. output file name. File names may be relative to 
;;           the current directory or absolute. 
;;

(send orff :answer :out '(target outfile)
      '((let (fobj acc)
	  (setf fobj (open outfile :direction :output))
	  (orff:pline ";; ~a" outfile)
	  (orff:pline ";; This file was automatically generated by orff.lsp")
	  (orff:pline ";;")
	  (orff:pline ";; Top-level function is ~a" target)
	  (orff:pline "")
	  
	  ;; Preliminaries
	  (dolist (r reqlist)
	    (orff:pline "(require '~a)" r))
	  (orff:pline "")

	  (orff:pline "(current-file \"~a\")" outfile)
	  (orff:pline "")

	  (if tempo
	      (progn
		(orff:pline "(set-tempo ~a)" tempo)
		(orff:pline "")))
		
	  
	  ;; Parts
	  (dolist (group parts)
	    (let (code lines)
	      (setf code (send (nth 2 group) :out
			       (nth 0 group)
			       (nth 1 group)
			       :pflag (nth 3 group)
			       :gflag (nth 4 group)))
	      (setf lines (su:split code (format nil "~%" code)))
	      (dolist (line lines)
		(orff:pline "~a" line))
	      (orff:pline "")
	      (orff:pline "")
	      ))
	  
	  ;; Top level function
	  (orff:pline "(defun ~a (&optional (reps 1))" target)
	  (orff:pline "  (sim")
	  (dolist (group parts)
	    (orff:pline "    (scale-db ~a (~a reps))" (nth 5 group)(nth 0 group)))
	  (orff:pline "))")
	  (orff:pline "")

	  (close fobj)
	  )))


#| Remove this line to execute example code  	      

;; @doc example orff
;; ***************************************************************************  
;;			      Example orff usage
;; ***************************************************************************  

;; The master cue list, a 2-bar phrase, repeated twice.
;; u = 's  c = 64
;;

(setf clst (list  0  3  4  8 11 12
		 16 19 20 24 27 28 30
		 32 35 36 40 43 44
		 48 51 52 56 59 60 61))
		 
		 		 
;; Possible pitch values, a simple pentatonic scale
;;

(setf nlst (list c3 d3 e3 g3 a3))


;; Create new orff object, initially there are no "parts".
;;

(setf orffobj (send orff :new clst :u 's :c 62 :pset nlst))


;; Make sure required instrument functions are loaded.
;;

(send orffobj :require "marimba")
(send orffobj :require "vibraphone")
(send orffobj :require "fmpiano")


;; Optionally set a temp, easily alterable later 
;;

(send orffobj :tempo 140)


;; Add "parts"
;;

(send orffobj :add "p1" "marimba" 8 :cmode 'RND :transpose 12)
(send orffobj :add "p2" "marimba" 12 :cmode 'SEQ :pmode 'SEQ )
(send orffobj :add "p3" "vibraphone" 5 :cmode 'RND)
(send orffobj :add "p4" "fmpiano" 12 :cmode 'SEQ :pmode 'RND :transpose 24)
(send orffobj :add "p5" "fmpiano" 16 :cmode 'RND :transpose -12)


;; Write the result to the current directory, hopefully this is on your XLISP
;; path.
;;

(send orffobj :out "foo" "orfftest.lsp")


;; The new score now needs to be loaded into Nyquist
;;

(load "orfftest")
(play (foo))


Main Page       Index