%-*- mode: Latex; abbrev-mode: true; auto-fill-function: do-auto-fill -*- %include lhs2TeX.fmt %include myFormat.fmt \out{ \begin{code} -- This code was automatically generated by lhs2tex --code, from the file -- HSoM/SelfSimilar.lhs. (See HSoM/MakeCode.bat.) \end{code} } \chapter{Self-Similar Music} \label{ch:self-similar} \begin{code} module Euterpea.Examples.SelfSimilar where import Euterpea \end{code} \index{self-similar music} \index{fractal music} In this chapter we will explore the notion of \emph{self-similar} music---i.e.\ musical structures that have patterns that repeat themselves recursively in interesting ways. There are many approaches to generating self-similar structures, the most well-known being \emph{fractals}, which have been used to generate not just music, but also graphical images. We will delay a general treatment of fractals, however, and will instead focus on more specialized notions of self-similarity, notions that we conceive of musically, and then manifest as Haskell programs. \section{Self-Similar Melody} \label{sec:self-sim-melody} Here is the first notion of self-similar music that we will consider: Begin with a very simple melody of |n| notes. Now duplicate this melody |n| times, playing each in succession, but first perform the following transformations: transpose the |i|th melody by an amount proportional to the pitch of the |i|th note in the original melody, and scale its tempo by a factor proportional to the duration of the |i|th note. For example, Figure \ref{fig:self-similar} shows the result of applying this process once to a four-note melody (the first four notes form the original melody). Now imagine that this process is repeated infinitely often. For a melody whose notes are all shorter than a whole note, it yields an infinitely dense melody of infinitesimally shorter notes. To make the result playable, however, we will stop the process at some pre-determined level. \begin{figure*} \centerline{ \epsfysize=2in \epsfbox{pics/self-sim.eps} } \caption{An Example of Self-Similar Music} \label{fig:self-similar} \end{figure*} How can this be represented in Haskell? A {\em tree} seems like it would be a logical choice; let's call it a |Cluster|: \begin{code} data Cluster = Cluster SNote [Cluster] type SNote = (Dur,AbsPitch) \end{code} This particular kind of tree happens to be called a {\em rose tree} \cite{}. An |SNote| is just a ``simple note,'' a duration paired with an absolute pitch. We prefer to stick with absolute pitches in creating the self-similar structure, and will convert the result into a normal |Music| value only after we are done. The sequence of |SNote|s at each level of the cluster is the melodic fragment for that level. The very top cluster will contain a ``dummy'' note, whereas the next level will contain the original melody, the next level will contain one iteration of the process described above (e.g.\ the melody in Figure \ref{fig:self-similar}), and so forth. To achieve this we will define a function |selfSim| that takes the initial melody as argument and generates an infinitely deep cluster: \indexhs{selfSim} \begin{code} selfSim :: [SNote] -> Cluster selfSim pat = Cluster (0,0) (map mkCluster pat) where mkCluster note = Cluster note (map (mkCluster . addMult note) pat) addMult :: SNote -> SNote -> SNote addMult (d0,p0) (d1,p1) = (d0*d1,p0+p1) \end{code} Note that |selfSim| itself is not recursive, but |mkCluster| is. This code should be studied carefully. In particualr, the recursion in |mkCluster| is different from what we have seen before, as it is not a direct invocation of |mkCluster|, but rather it is a high-order argument to |map| (which in turn invokes |mkCluster| an aribtrary number of times). Next, we define a function to skim off the notes at the $n^{th}$ level, or $n^{th}$ ``fringe,'' of a cluster: \begin{code} fringe :: Int -> Cluster -> [SNote] fringe 0 (Cluster note cls) = [note] fringe n (Cluster note cls) = concatMap (fringe (n-1)) cls \end{code} \syn{|concatMap| is defined in the Standard Prelude as: \begin{spec} concatMap :: (a -> [b]) -> [a] -> [b] concatMap f = concat . map f \end{spec} Recall that |concat| appends together a list of lists, and is defined in the Prelude as: \begin{spec} concat :: [[a]] -> [a] concat = foldr (++) [] \end{spec} } All that is left to do is convert this into a |Music| value that we can play: \begin{spec} simToMusic :: [SNote] -> Music Pitch simToMusic ss = let mkNote (d,ap) = note d (pitch ap) in line (map mkNote ss) \end{spec} We can define this with a bit more elegance as follows: \begin{code} simToMusic :: [SNote] -> Music Pitch simToMusic = line . map mkNote mkNote :: (Dur,AbsPitch) -> Music Pitch mkNote (d,ap) = note d (pitch ap) \end{code} The increased modularity will allow us to reuse |mkNote| later in the chapter. Putting it all together, we can define a function that takes an initial pattern, a level, a number of pitches to transpose the result, and a tempo scaling factor, to yield a final result: \begin{code} ss pat n tr te = transpose tr $ tempo te $ simToMusic $ fringe n $ selfSim pat \end{code} \subsection{Sample Compositions} Let's start with a melody with no rhythmic variation. \begin{code} m0 :: [SNote] m0 = [(1,2),(1,0),(1,5),(1,7)] tm0 = instrument Vibraphone (ss m0 4 50 20) \end{code} One fun thing to do with music like this is to combine it with variations of itself. For example: \begin{code} ttm0 = tm0 :=: transpose (12) (revM tm0) \end{code} We could also try the opposite: a simple percussion instrument with no melodic variation, i.e.\ all rhythm: \begin{code} m1 :: [SNote] m1 = [(1,0),(0.5,0),(0.5,0)] tm1 = instrument Percussion (ss m1 4 43 2) \end{code} Note that the pitch is transposed by 43, which is the MIDI Key number for a ``high floor tom'' (i.e.\ percussion sound |HighFloorTom|---recall the discussion in Section \ref{sec:percussion}). Here is a very simple melody, two different pitches and two different durations: \begin{code} m2 :: [SNote] m2 = [(dqn,0),(qn,4)] tm2 = ss m2 6 50 (1/50) \end{code} Here are some more exotic compositions, combining both melody and rhythm: \begin{code} m3 :: [SNote] m3 = [(hn,3),(qn,4),(qn,0),(hn,6)] tm3 = ss m3 4 50 (1/4) ttm3 = let l1 = instrument Flute tm3 l2 = instrument AcousticBass $ transpose (-9) (revM tm3) in l1 :=: l2 m4 :: [SNote] m4 = [ (hn,3),(hn,8),(hn,22),(qn,4),(qn,7),(qn,21), (qn,0),(qn,5),(qn,15),(wn,6),(wn,9),(wn,19) ] tm4 = ss m4 3 50 8 \end{code} % $ %% p3 = [(6/10,2),(13/10,5),(wn,0),(9/10,7)] %% ss3 = ss p3 4 50 20 \newpage \vspace{.1in}\hrule \begin{exercise}{\em Experiment with this idea futher, using other melodic seeds, exploring different depths of the clusters, and so on.} \end{exercise} \begin{exercise}{\em Note that |concat| is defined as |foldr (++) []|, which means that it takes a number of steps proportional to the sum of the lengths of the lists being concatenated; we cannot do any better than this. (If |foldl| were used instead, the number of steps would be proportional to the number of lists times their average length.) However, |fringe| is not very efficient, for the following reason: |concat| is being used over and over again, like this: \begin{spec} concat [ concat [ ... ], concat [ ... ], concat [ ... ] ] \end{spec} This causes a number of steps proportional to the depth of the tree times the length of the sub-lists; clearly not optimal. Define a version of |fringe| that is linear in the total length of the final list.} \end{exercise} \vspace{.1in}\hrule \section{Self-Similar Harmony} \label{sec:self-sim-harmony} In the last section we used a melody as a seed, and created longer melodies from it. Another idea is to stack the melodies vertically. Specifically, suppose we redefine |fringe| in such a way that it does not concatenate the sub-clusters together: \begin{code} fringe' :: Int -> Cluster -> [[SNote]] fringe' 0 (Cluster note cls) = [[note]] fringe' n (Cluster note cls) = map (fringe (n-1)) cls \end{code} Note that this strategy is only applied to the top level---below that we use fringe. Thus the type of the result is |[[SNote]]|, i.e.\ a list of lists of notes. We can convert the individual lists into melodies, and play the melodies all together, like this: \begin{code} simToMusic' :: [[SNote]] -> Music Pitch simToMusic' = chord . map (line . map mkNote) \end{code} Finally, we can define a function akin to |ss| defined earlier: \begin{code} ss' pat n tr te = transpose tr $ tempo te $ simToMusic' $ fringe' n $ selfSim pat \end{code} Using some of the same patterns used earlier, here are some sample compositions (with not necessarily a great outcome...): \begin{code} ss1 = ss' m2 4 50 (1/8) ss2 = ss' m3 4 50 (1/2) ss3 = ss' m4 3 50 2 \end{code} \out{ p1 = [(hn,3),(qn,4),(qn,0),(wn,6)] p2 = [(hn,0),(wn,4),(hn,7),(wn,5)] p3 = [(6/10,2),(13/10,5),(wn,0),(9/10,7)] p4 = [(hn,3),(hn,8),(hn,22),(qn,4),(qn,7),(qn,21), (qn,0),(qn,5),(qn,15),(wn,6),(wn,9),(wn,19)] } Here is a new one, based on a major triad: \begin{code} m5 = [(en,4),(sn,7),(en,0)] ss5 = ss m5 4 45 (1/500) ss6 = ss' m5 4 45 (1/1000) \end{code} Note the need to scale the tempo back drastically, due to the short durations of the starting notes. \section{Other Self-Similar Structures} The reader will observe that our notion of ``self-similar harmony'' does not involve changing the structure of the |Cluster| data type, nor the algorithm for computing the sub-structures (as captured in |selfSim|). All that we do is interpret the result differently. This is a common characteristic of algorithmic music composition---the same mathematical or computational structure is interpreted in different ways to yield musically different results. For example, instead of the above strategy for playing melodies in parallel, we could play entire levels of the |Cluster| in parallel, where the number of levels that we choose is given as a parameter. If alligned properly in time there will be a harmonic relationship between the levels, which could yield pleasing results. The |Cluster| data type is conceptually useful in that is represents the infinite solution space of self-simlar melodies. And it is computationally useful in that it is computed to a desired depth only once, and thus can be inspected and reused without recomputing each level of the tree. This idea might be useful in the application mentioned above, namely combining two or more levels of the result in interesting ways. However, the |Cluster| data type is strictly unnecessary, in that, for example, if we are interested in computing a specific level, we could define a function that recursed to that level and gave the result directly, without saving the intermediate levels. A final point about the notion of self-similarity captured in this chapter is that the initial pattern is used as the basis with which to transform each successive level. Another strategy would be to use the entirety of each new level as the seed for transforming itself into the next level. This will result in an exponential blow-up in the size of each level, but may be worth pursuing---in some sense it is a simpler notion of self-similarity than what we have used in this chapter. All of the ideas in this section, and others, we leave as exercises for the reader. \vspace{.1in}\hrule \begin{exercise}{\em Experiment with the self-similar programs in this chapter. Compose an interesting piece of music through a judicious choice of starting melody, depth of recursion, instrumentation, etc.} \end{exercise} \begin{exercise}{\em Devise an interpretation of a |Cluster| that plays multiple levels of the |Cluster| in parallel. Try to get the levels to align properly in time so that each level has the same duration. You may choose to play all the levels up to a certain depth in parallel, or levels within a certain range, say levels 3 through 5.} \end{exercise} \begin{exercise}{\em Define an alternative version of |simToMusic| that interprets the music differently. For example: \begin{itemize} \item Interpret the pitch as an index into a scale---e.g., as an index into the C major scale, so that 0 corresponds to C, 1 to D, 2 to E, 3 to F, ..., 6 to B, 7 to C in the next octave, and so on. \item Interpret the pitch as duration, and the duration as pitch. \end{itemize} } \end{exercise} \begin{exercise}{\em Modify the self-similar code in the following ways: \begin{itemize} \item Add a Volume component to |SNote| (in other words, define it as a triple instead of a pair), and redefine |addMult| so that it takes two of these triples and combines them in a suitable way. Then modify the rest of the code so that the result is a |Music1| value. With these modifications, compose something interesting that highlights the changes in volume. \item Change the |AbsPitch| field in |SNote| to be a list of |AbsPitch|s, to be interpreted ultimately as a chord. Figure out some way to combine them in |addMult|, and compose something interesting. \end{itemize} } \end{exercise} \begin{exercise}{\em Devise some other variant of self-similar music, and encode it in Haskell. In particular, consider structures that are different from those generated by the |selfSim| function.} \end{exercise} \begin{exercise}{\em Define a function that gives the same result as |ss|, but without using a data type such as |Cluster|.} \end{exercise} \begin{exercise}{\em Define a version of self-similarity similar to that defined in this chapter, but that uses the entire melody generated at one level to transform itself into the next level (rather than using the original seed pattern).} \end{exercise} \vspace{.1in}\hrule