OMN-utils

Function summary
copy-time-signature music-with-time-signature music-to-rebar
count-notes notes
edit-omn type notation fun &key (flat nil) (swallow nil) (section nil) (additional-args nil)
ensure-double-list x
flattened-length-adjust duration sequence
fn-unfold fns sequence
length-add &rest length-values
length-subtract &rest length-values
map-events fn sequence &key (test #'(lambda (&rest args) (declare (ignore args)) t)) flat section exclude
map-omn fn omn-expr
map-position-in-bar position type sequence fun &key (section nil)
map-section function sequence &key section exclude section-args shared-args
mk-seed &optional seed
phrase-lengths lengths
process-element fn element args
process-omn2 type function sequence &key flatten flat (span :length) swallow section exclude
rnd-section section-range probability &key seed
swap-args fn &optional (pos 1)
total-duration sequence &optional float?
*< sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*<> sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*> sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*>< sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*a sequence range &key (type :transpose) (section nil) (exclude nil) (omn nil)
*ac sequence size &key (unique t) (section nil) (exclude nil)
*frag sequence count range &key (encode t) (lists nil) (section nil) (exclude nil) (seed nil)
*i sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*ld sequence values &key set ignore (seed nil) (section nil) (exclude nil) (omn nil)
*mute sequence &key (section nil) (exclude nil)
*r sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*rest sequence value &key (type nil) (swallow t) (section nil) (exclude nil) (omn nil) (flat nil) (span :length)
*ri sequence &key (transpose nil) (section nil) (exclude nil) (omn t)
*t sequence transpose &key (section nil) (exclude nil) (ambitus 'piano) (omn nil)
map-events   fn sequence &key (test #'(lambda (&rest args) (declare (ignore args)) t)) flat section exclude  [Function]

Every event for which the function `test' returns true is transformed by the function `fn'. In the background, sequence is transformed into a list of events, where each note is represented by a list of the parameters length, pitch, velocity, and articulation.

Rests are skipped unprocessed.

Arguments:

  • fn: function expecting and returning a single event, i.e. the function expects the arguments length, pitch, velocity and articulation of individual elements.

  • sequence: an OMN sequence

  • test: Boolean function expecting a single event. By default, all elements are processed.

  • flat (Boolean): whether or not to flatten sequence before processing.

  • section (list of ints): 0-based positions of bars (sublists) in nested `sequence' to which `fn' is applied.

  • exclude (list of ints): 0-based positions of bars (sublists) in nested `sequence' to which `fn' is *not* applied. Only either `section' or `exclude' should be specified, otherwise `exclude' is ignored.

Examples:

Reduce all events with velocity p to velocity pp

    (map-events 
      #'(lambda (l p v a) (list l p 'pp a)) 
      '((-e s bb3 f marc a3 leg g3 p leg gs3 leg g3 leg a3 leg) (q fs3 f ten -q)) 
      :test #'(lambda (l p v a) (eql v 'p))) 
process-element   fn element args  [Function]

Many Opusmodus functions are defined to work only with lists. This function is intended to help when you want to instead process a single element with such a function.

Examples:

Transpose a single element with pitch-transpose

    (process-element #'pitch-transpose 'c4 '(2 _)) 

Without this function, the call above would look as follows.

    (first (pitch-transpose 2 (list 'c4))) 

It is a matter of taste/style, which approach you prefer :)

Of course, it might be better if instead Opusmodus functions would simply support single OMN notation elements as well.

map-omn   fn omn-expr  [Function]

Variant of mapcar for omn expressions, intended for creating variations of omn-expr. Applies function fn to every note in omn-expr (a flat OMN list). fn must exect four arguments (a length, pitch, velocity and articution) and returns a list of four values (a length, pitch, velocity and articution).

NOTE: This was one of my first Opusmodus function definitions, and while it works it is not as refined as some later functions :)

Arguments:

  • fn: a function expecting four arguments (a length, pitch, velocity and articulation) and returning a list of four values (a length, pitch, velocity and articulation).

  • omn-expr: an OMN expression

Examples:

    (map-omn #'(lambda (length pitch velocity articulation) 
                  (list length  
                        pitch  
                        ;; replace tasto dynamics by fff 
                        (if (equal articulation 'tasto) 
                          'fff 
                          velocity) 
                        articulation)) 
              '(e. c4 pppp tasto d4 ponte e4)) 
     => (e. c4 fff tasto d4 pppp ponte e4) 

    (map-omn #'(lambda (length pitch velocity articulation) 
                  (list length  
                              (if (member 'slap (disassemble-articulations articulation)) 
                                'c4 
                                pitch) 
                              velocity 
                              articulation)) 
              '((q b4 f slap+stacc -h q bb4 slap+stacc -h) (q gs4 slap+stacc -h) (q bb4 slap+stacc c5 mp ord d5 q. f5 e eb5 q d5) (-q c5 g4 h fs4 q eb5 stacc) (q c5 f slap+stacc -h q. g4 mp ord e f5 q e5) (q f5 cs5 f4 h d5 -q))) 

BUGS:

Does not work if omn-expr contains rest.

Problem: omn does not provide any values for rests. Possible solution: couple note durations with their respective params, but leave rests without. Then skip rests in the processing unchanged. BTW: This process looses articulations on rests, like fermata.

Notes:

See also the Opusmodus built-in function `single-events': looping (or mapping) over its result has similar effect.

See Also:

map-events

copy-time-signature   music-with-time-signature music-to-rebar  [Function]

Rebars `music-to-rebar' so that it fits the meter of `music-with-time-signature'. If music-with-time-signature is a flat list, no rebarring happens.

map-section   function sequence &key section exclude section-args shared-args  [Function]

Apply a function to only selected bars (sublists) in an OMN sequence.

Arguments:

  • function: function to apply to sublists in `sequence'

  • sequence: nested list of OMN parameters or full OMN expressions

  • section (list of ints): 0-based positions of bars (sublists) in `sequence' to which `function' is applied.

  • exclude (list of ints): 0-based positions of bars (sublists) in `sequence' to which `function' is *not* applied. Only either `section' or `exclude' should be specified, otherwise `exclude' is ignored.

  • section-args (list or list of lists): Further arguments to `function' added behind the current sublist of `sequence'. If not a nested list, then only a single additional argument is specified for each bar (sublist) to which `function' is applied.

  • shared-args (list): Further arguments to `function' added behind the current sublist of `sequence' and potentially `section-args'.

Examples:

    (map-section #'(lambda (seq) (pitch-transpose 7 seq)) '((c4 c4 c4) (c4 c4 c4) (c4 c4 c4)) :section '(1 2)) 

    (map-section #'(lambda (seq) (pitch-transpose 7 seq)) '((c4 c4 c4) (c4 c4 c4) (c4 c4 c4)) :exclude '(0)) 

    (map-section #'(lambda (seq interval) (pitch-transpose interval seq)) '((c4 c4 c4) (c4 c4 c4) (c4 c4 c4))  
                  :section '(1 2) 
                  :shared-args '(7)) 

    (map-section #'(lambda (seq interval) (pitch-transpose interval seq)) '((c4 c4 c4) (c4 c4 c4) (c4 c4 c4))  
                  :section '(1 2) 
                  :section-args '(7 12)) 

    (map-section #'(lambda (seq count divide)  
                      (length-divide count divide seq)) 
                  '((q q q) (q q q) (q q q) (q q q))  
                  :section '(1 2 3) 
                  :section-args '((1 2) (2 3))) 

    (map-section #'(lambda (seq count divide &rest args)  
                      (apply #'length-divide count divide seq args)) 
                  '((q q q) (q q q) (q q q) (h.))  
                  :section '(1 2 3) 
                  :section-args '((1 2) (2 3)) 
                  :shared-args '(:ignore h.)) 

See Also:

This function is a generalised and somewhat more clean variant of the Opusmodus builtin `do-section'.

edit-omn   type notation fun &key (flat nil) (swallow nil) (section nil) (additional-args nil)  [Function]

Use function `fun', defined for transforming lists of individual OMN parameters of `type' (e.g., :length, or :velocity) to transform omn expression `notation'. This function is intended as a convenient way to generalise your functions to support omn notation as input.

Arguments:

  • type: a keyword like :length, :pitch, :velocity, :duration, or :articulation (any keyword supported by function omn or make-omn).

  • notation: a omn sequence or a plain parameter list (can be nested).

  • fun: a function expecting a parameter sequence of given type. It is sufficient to support only a flat input list, support for nested lists is added implicitly.

  • flat: whether or not `fun' expects a flat input list.

  • swallow: if `type' is :length, and `fun' turns notes into rests, the argument `swallow' sets whether the pitches of these notes should be shifted to the next note or omitted (swallowed). `swallow' is ignored if notation is a plain parameter list (e.g., a

  • section: only process the sublists (bars) at the positions given to this argument. Arg is ignored if `flat' is T.

  • additional-args (list of args): `additional-args' allows implementing 'dynamic' arguments, i.e., transformations that change over the sublists of `notation' depending on a list of arguments instead of a plain value. If `additional-args' is nil, then `fun' expects parameter values directly. However, if it is a list, then `fun' expects a list where the parameter values are the first element, and `additional-args' (if `flat' is T) or an element thereof (if `flat' is NIL) the second element in the list expected by `fun'.

Examples:

Roll your own transposition function.

First define an aux def supporting only a flat list of pitches.

    (defun my-transposition-aux (interval pitches) 
       (midi-to-pitch (loop for p in (pitch-to-midi pitches) 
                            collect (+ p interval)))) 

Test that function.

    (my-transposition-aux 7 '(c4 e4 g4))  
      => (g4 b4 d5) 

Now, based on that aux function, define a function that supports also full OMN sequences. You can later expand this new function further with edit-omn to also support arguments like section and flat (see below).

    (defun my-transposition (interval omn) 
       (edit-omn :pitch omn 
                 #'(lambda (ps) (my-transposition-aux interval ps)))) 

Test the new function with nested OMN including rests.

    (my-transposition 7 '((q c4 mp -q q e4 q f4) (h g4 tr2))) 
      => ((q g4 mp - b4 c5) (h d5 mp tr2)) 

Another example: expand the built-in function `length-rest-series' to support arbitrary OMN expressions (not just length lists), and additionally the arguments `swallow' and `section'.

    (defun note-rest-series (positions sequence &key (flat nil) (swallow nil) (section nil)) 
       (edit-omn :length sequence  
                 #'(lambda (ls) (length-rest-series positions ls)) 
                 :swallow swallow 
     	        :section section 
     	        :flat flat)) 
      
     (setf melody '((s eb6 < leg f5 < leg c5 < leg f5 < leg) (e e6 f - -q))) 
     (note-rest-series '(1 1) melody :swallow T :section '(0)) 

The next example demonstrates how 'dynamic' arguments can be implemented, i.e. arguments that support different values for subsections. Below is a simplified definition of the function rotate-omn. Note how the function argument `n' is handed to the argument `additional-args' of `edit-omn' if `n' is a list. The function given to `edit-omn' also tests whether `n' is a list, and in that case extracts the OMN sublist to rotate as first element of the function argument `xs' and the amount of the rotation of this sublist as second element of `xs'. Further 'dynamic' arguments could be implemented by handing `additional-args' a list of argument lists to use, and by then extracting the relevant elements of such sublists within the function given to `edit-omn'.

    (defun rotate-omn (n sequence &key (parameter :pitch) (flat T) (section nil)) 
       (let ((n-list-arg? (listp n))) 
         (edit-omn parameter sequence 
     	          #'(lambda (xs) 
     		      (if n-list-arg? 
     		          (gen-rotate (second xs) (first xs)) 
     		          (gen-rotate n xs))) 
     	          :section section 
     	          :flat flat 
     	          :additional-args (when n-list-arg? n)))) 

The function rotate-omn can now be called with either giving a single number or a list of numbers to its argument `n'.

    (setf melody '((-h e c4 e4) (q. f4 e g4 q a4) (q g4 f4 e e4 d4))) 
      
     (rotate-omn 1 melody) ; default parameter pitch 
      
     (rotate-omn '(0 1 2) melody :flat nil)  
      
     (rotate-omn '(2 1) melody :section '(1 2) :flat nil :parameter :length) 

process-omn2   type function sequence &key flatten flat (span :length) swallow section exclude  [Function]

Function similar to edit-omn that will soon be built-in in Opusmodus.

map-position-in-bar   position type sequence fun &key (section nil)  [Function]

Transforms in the bars of `sequence' the parameter of `type' (e.g., :length) at `position' with `fun'.

Examples:

Apply the articulation tenuto to every first note in all bars except the last bar.

    (map-position-in-bar 0 :articulation  
                          '((-q c4 c4) (q c4 c4 c4) (q c4 c4 c4))  
                          #'(lambda (ignore) 'ten) 
                          :section '(0 1)) 

Notes:

Currently, rests are simply not counted when estimating the position of a parameter other then :length. Potential workaround: use argument `section'.

total-duration   sequence &optional float?  [Function]

Returns the total duration (length) of `sequence', i.e. the sum of the length of all its notes and rests.

If `float?' is true the result is a float.

Examples:

    (total-duration '((h c4 q) (q h tie) (h.))) 
     => 9/4 
flattened-length-adjust   duration sequence  [Function]

Currently, the built-in function length-adjust has no :flatten argument. This function offers a workaround.

count-notes   notes  [Function]

Returns number of notes (ignoring rests) in length list or other OMN expression.

Examples:

    (count-notes '((q c4 c4 c4) (q g4 g4 g4))) 

* BUG:

Counts tied notes as multiple notes.

phrase-lengths   lengths  [Function]

Returns the number of notes between rests in the given lengths.

Arguments:

  • length: lengths or OMN (list or list of list).

length-subtract   &rest length-values  [Function]

Subtraction for OMN length values.

Examples:

    (length-subtract 'w 'q) 
     => h. 

length-add   &rest length-values  [Function]

Addition of OMN length values.

Examples:

    (length-add 'w 'q) 
     => wq 
rnd-section   section-range probability &key seed  [Function]

The function returns a list of random section numbers intended for the argument section of many Opusmodus functions. The list of returned sections is unsorted.

Arguments:

  • section-range (pair of ints): the range of 0-based section positions (including boundaries) within which sections are returned.

  • probability (float in interval 0-1): the likelyhood by which sections are return, where 0 means the result is nil, 1 means that the result contains all sections within the given range, and, e.g., 0.5 means a 50 percent probability that any section is selected.

Examples:

    (rnd-section '(0 9) 0.5 :seed 1) 
mk-seed   &optional seed  [Function]

Generates a random seed value, prints and returns it. Useful for exploring different results of random processes, but then keeping a found solution.

This function is now rather redundant, as Opusmodus automatically prints seed values of all function calls.

Arguments:

  • seed (int): optionally fixes generated seed.

Examples:

    (rnd-sample 3 '(c4 d4 e4) :seed (mk-seed)) 
     ; 405621 rnd-sample 
     => (c4 e4 d4)  

    (rnd-sample 3 '(c4 d4 e4) :seed (mk-seed 13)) 
     ; 13 rnd-sample 
     => (e4 d4 e4)  

ensure-double-list   x  [Function]

Ensures that `x' is a duble-wrapped list. If not, a list (or two) are wrapped around it. As a precaution, if `x' is inconsistently nested, then the result is a flattened version of it with a double list wrapped around.

fn-unfold   fns sequence  [Function]

Much like the buildin Opusmodus `unfold`, but instead works with functions and additional arguments can be given to the functions. Apply to `sequence` all fns in order.

Arguments:

  • fns (list of lists): Each sublist has the form (<omn-fn> &rest <args>), where <omn-fn> is a function expecting an OMN sequence as first argument and arbitrary further argments, and <args> are the further arguments beyond the OMN sequence given to the function.

  • sequence: OMN sequence

Examples:

Some material to use

    (setf mat '((q c4 d4 e4) (h f4 q b3))) 

Remember: all functions used must expect a OMN sequence as *first* argument.

    (fn-unfold '((gen-retrograde :flatten T) (quantum :fraction -0.2)) mat) 

Some short-hand versions of common functions are defined for conciseness. These short-hand functions commonly start with an asterisk (*) to stand out and to reduce namespace pollution.

    (fn-unfold '((*t 12) (*ld (2 3) :section 1)) mat) 
swap-args   fn &optional (pos 1)  [Function]

Return a function where the argument at `pos` is moved forward to become the first positional argument. Intended for making arbitrary OMN functions usable for `fn-unfold` (so that their OMN argument becomes the first positional argument).

*t   sequence transpose &key (section nil) (exclude nil) (ambitus 'piano) (omn nil)  [Function]

Like pitch-transpose, but sequence as first param.

*mute   sequence &key (section nil) (exclude nil)  [Function]

Alias for gen-pause.

*a   sequence range &key (type :transpose) (section nil) (exclude nil) (omn nil)  [Function]

Like ambitus, but sequence as first param.

*ac   sequence size &key (unique t) (section nil) (exclude nil)  [Function]

Like ambitus-chord, but sequence as first param.

*r   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return retrograde.

*i   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return inverse.

*ri   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return retrograde inverse.

*>   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return descending.

*<   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return ascending.

*><   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return descending-ascending.

*<>   sequence &key (transpose nil) (section nil) (exclude nil) (omn t)  [Function]

Simplification of pitch-variant: return ascending-descending.

*ld   sequence values &key set ignore (seed nil) (section nil) (exclude nil) (omn nil)  [Function]

Like length-divide, but sequence as first param.

*frag   sequence count range &key (encode t) (lists nil) (section nil) (exclude nil) (seed nil)  [Function]

Like gen-fragment, but sequence as first param.

*rest   sequence value &key (type nil) (swallow t) (section nil) (exclude nil) (omn nil) (flat nil) (span :length)  [Function]

Like length-to-rest, but sequence as first param.