%-*- 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/SigFuns.lhs. (See HSoM/MakeCode.bat.) \end{code} } \chapter{Euterpea's Signal Functions} \label{ch:sigfuns} \begin{code} {-# LANGUAGE Arrows #-} module Euterpea.Examples.SigFuns where import Euterpea import Control.Arrow ((>>>),(<<<),arr) \end{code} \syn{The first line in the module header above is a \emph{compiler pragma}, amd in this case is telling GHC to accept \emph{arrow syntax}, which will be explained in Section~\ref{sec:sigfuns}.} In this chapter we show how the theoretical concepts involving sound and signals studied in the last chapter are manifested in Euterpea. The techniques learned will lay the groundwork for doing two broad kinds of activities: \emph{sound synthesis} and \emph{audio processing}. Sound synthesis might include creating the sound of a footstep on dry leaves, simulating a conventional musical instrument, creating an entirely new instrument sound, or composing a single ``soundscape'' that stands alone as a musical composition. Audio processing includes such things as equalization, filtering, reverb, special effects, and so on. In future chapters we will study various techniques for achieving these goals. %% apply these concepts to particular computer music applications. \section{Signals and Signal Functions} \label{sec:sigfuns} %% Conceptually, one could think of a signal as a value of type |Signal %% T| that represents time-varying values of type |T|. For example, %% |Signal Float| would be a time-varying floating-point number, |Signal %% AbsPitch| would be a time-varing absolute pitch, and so on. %% Abstractly, one could therefore think of a signal as a function: %% \begin{spec} %% Signal a ==== Time -> a %% \end{spec} %% where |Time| is some suitable representation of time. As we saw in Chapter \ref{ch:MUI}, it would seem natural to represent a signal as an abstract type, say |Signal T| in Haskell, and then define functions to add, multiply, take the sine of, and so on, signals represented in this way. For example, |Signal Float| would be the type of a time-varying floating-point number, |Signal AbsPitch| would be the type of a time-varing absolute pitch, and so on. Then given |s1,s2 :: Signal Float| we might simply write |s1 + s2|, |s1 * s2|, and |sin s1| as examples of applying the above operations. Haskell's numeric type class hierarchy would make this particularly easy to do. Indeed, several domain-specific languages based on this approach have been defined before, beginning with the language \emph{Fran} \cite{Fran} that was designed for writing computer animation programs. But years of experience and theoretical study have revealed that such an approach leads to a language with subtle time- and space-leaks,\footnote{A time-leak in a real-time system occurs whenever a time-dependent computation falls behind the current time because its value or effect is not needed yet, but then requires ``catching up'' at a later point in time. This catching up process can take an arbitrarily long time, and may consume additional space as well. It can destroy any hope for real-time behavior if not managed properly.} for reasons that are beyond the scope of this textbook \cite{Leak07}. Therefore Euterpea takes a somewhat different approach, as described below. %% Earlier versions of Fran, FAL \cite{SOE}, and FRP \cite{Yale-FRP} used %% various methods to make this performance problem less of an issue, but %% ultimately they all either suffered from the problem in one way or %% another, or introduced other problems as a result of fixing it. Perhaps the simplest way to understand Euterpea's approach to programming with signals is to think of it as a language for expressing \emph{signal processing diagrams} (or equivalently, electrical circuits). We refer to the lines in a typical signal processing diagram as \emph{signals}, and the boxes that convert one signal into another as \emph{signal functions}. For example, this very simple diagram has two signals, |x| and |y|, and one signal function, |sigfun|: \begin{center} \includegraphics[scale=0.70]{pics/frp-circuit} \end{center} Using Haskell's \emph{arrow syntax} \cite{Hughes2000,Paterson2001}, this diagram can be expressed as a code fragment in Euterpea simply as: \begin{spec} y <- sigfun -< x \end{spec} \syn{The syntax |<-| and |-<| is typeset here in an attractive way, but the user will have to type \verb+<-+ and \verb+-<+, respectively, in her source file.} Arrows and arrow syntax will be described in much more detail in Chapter~\ref{ch:implementing-sigfuns}. For now, keep in mind that |<-| and |-<| are part of the \emph{syntax}, and are not simply binary operators. Indeed, we can't just write the above code fragment anywhere. It has to be within an enclosing |proc| construct whose result type is that of a signal function. The |proc| construct begins with the keyword |proc| along with an argument, analogous to an anonymous function. For example, a signal function that takes a signal of type |Double| and adds 1 to every signal sample, and then applies |sigfun| to the resulting signal, can be written: \begin{spec} proc y -> do x <- sigfun -< y+1 outA -< x \end{spec} \syn{The |do| keyword in arrow syntax introduces layout, just as it does in monad syntax.} %% Also, modules that use the arrow syntax should have a %% ``.as'' or ``.lhs'' (instead of ``.hs'') extension.} Note the analogy of this code to the following snippet involving an ordinary anonymous function: \begin{spec} \ y -> let x = sigfun (y+1) in x \end{spec} The important difference, however, is that |sigfun| works on a signal, which we can think of as a stream of values, whose representative values at the ``point'' level are the variables |x| and |y| above. So in reality we would have to write something like this: \begin{spec} \ ys -> let xs = sigfun (map (+1) ys) in xs \end{spec} to achieve the effect of the arrow code above. The arrow syntax allows us to avoid worrying about the streams themselves. It also has other important advantages that are beyond the scope of the current discussion. Arrow syntax is just that-–-syntactic sugar that is expanded into a set of conventional functions that work just as well, but are more cumbersome to program with (just as with monad syntax). This syntactic expansion will be described in more detail in Chapter~\ref{ch:implementing-sigfuns}. To use the arrow syntax within a ``.lhs'' file, one must declare a compiler flag in GHC at the very beginning of the file, as follows: \begin{spec} {-# LANGUAGE Arrows #-} \end{spec} %% We can also create and use signal functions that operate on tuples of %% signals. For example, a signal function |exp :: SigFun (Double, %% Double) Double| that raises its first argument to the power of its %% second, at every point in time, could be used as follows: %% \begin{code} %% z <- exp -< (x,y) %% \end{code} \subsection{The Type of a Signal Function} \label{sec:sigfun-type} Polymorphically speaking, a signal function has type: \begin{spec} Clock c => SigFun c a b \end{spec} which should be read, ``for some clock type (i.e.\ sampling rate) |c|, this is the type of signal functions that convert signals of type |a| into signals of type |b|.'' \out{ \syn{|Signal| is actually not a good name for the type---it should be something like |SignalFunction| or |SF| and will probably be renamed in a soon-to-be-released version of Euterpea.} } The type variable |c| indicates what clock rate is being used, and for our purposes will always be one of two types: |AudRate| or |CtrRate| (for \emph{audio rate} and \emph{control rate}, respectively). Being able to express the sampling rate of a signal function is what we call \emph{clock polymorphism}. Although we like to think of signals as continuous, time-varying quantities, in practice we know that they are sampled representations of continous quantities, as discussed in the last chapter. However, some signals need to be sampled at a very high rate---say, an audio signal---whereas other signals need not be sampled at such a high rate---say, a signal representing the setting of a slider. The problem is, we often want to mix signals sampled at different rates; for example, the slider might control the volume of the audio signal. One solution to this problem would be to simply sample everything at the very highest rate, but this is computationally inefficient. A better approach is to sample signals at their most appropriate rate, and to perform coercions to ``up sample'' or ``down sample'' a signal when it needs to be combined with a signal sampled at a different rate. This is the approach used in Euterpea. More specifically, the base type of each signal into and out of a signal function must satisfy the type class constraint |Clock c|, where |c| is a \emph{clock type}. The |Clocked| class is defined as: \begin{spec} class Clock c where rate :: c -> Double \end{spec} The single method |rate| allows the user to extract the sampling rate from the type. In Euterpea, the |AudRate| is pre-defined to be 44.1 kHz, and the |CtrRate| is set at 4.41 kHz. Here are the definitions of |AudRate| and |CtrRate|, along with their instance declarations in the |Clock| class, to achieve this: \begin{spec} data AudRate data CtrRate instance Clock AudRate where rate _ = 44100 instance Clock CtrRate where rate _ = 4410 \end{spec} Because these two clock types are so often used, it is helpful to define a couple of type synonyms: \begin{spec} type AudSF a b = SigFun AudRate a b type CtrSF a b = SigFun CtrRate a b \end{spec} From these definitions it should be clear how to define your own clock type. \syn{Note that |AudRate| and |CtrRate| have no constructors---they are called \emph{empty} data types. More precisely, they are each inhabited by exactly one value, namely |bottom|.} The sampling rate can be determined from a given clock type. In this way, a coercion function can be written to change a signal sampled at one rate to a signal sampled at some other rate. In Euterpea, there are two such functions that are pre-defined: \begin{spec} coerce, upsample :: (Clock c1, Clock c2) => SigFun c1 a b -> SigFun c2 a b \end{spec} The function |coerce| looks up the sampling rates of the input and output signals from the type variables |c1| and |c2|. It then either stretches the input stream by duplicating the same element or contracts it by skipping elements. (It is also possible to define a more accurate coercion function that performs interpolation, at the expense of performance.) For simpler programs, the overhead of calling |coerce| might not be worth the time saved by generating signals with lower resolution. (Haskell’s fractional number implementation is relatively slow.) The specialized coercion function |upsample| avoids this overhead, but only works properly when the output rate is an integral multiple of the input rate (which is true in the case of |AudRate| and |CtrRate|). Keep in mind that one does not have to commit a signal function to a particular clock rate---it can be left \emph{polymorphic}. Then that signal function will adapt its sampling rate to whatever is needed in the context in which it is used. %% From a typing perspective, signal functions such as |sigfun| will have %% a type of the form |SigFun T1 T2|, for some types |T1| and |T2|, in which %% case |x| will have type |T1|, and |y| will have type |T2|. Although %% signal functions act on signals, the arrow notation allows one to %% manipulate the instantaneous values of the signals, such as |x| and %% |y| above. Not suprisingly, the actual representation of the type SigFun %% is hidden (i.e.\ |SigFun| is abstract), Also keep in mind that a signal function is an abstract function. You cannot just apply it to an argument like an ordinary function---that is the purpose of the arrow syntax. There are no values that directly represent \emph{signals} in Euterpea---there are only signal \emph{functions}. The arrow syntax provides a convenient way to compose signal functions together---i.e.\ to wire together the boxes that make up a signal processing diagram. By not giving the user direct access to signals, and providing a disciplined way to compose signal functions (namely arrow syntax), time- and space-leaks are avoided. In fact, the resulting framwework is highly amenable to optimization, although this requires using special features in Haskell, as described in Chapter \ref{ch:implementing-sigfuns}. A signal function whose type is of the form |Clock c => SigFun c () b| essentially takes no input, but produces some output of type |b|. Because of this we often refer to such a signal function as a \emph{signal source}. %% A Euterpea program program expresses the composition of a %% possibly large number of signal functions into a composite signal %% function that is then ``run'' at the top level by a suitable %% interpreter. A good analogy for this idea is a state or IO monad, %% where the state is hidden, and a program consists of a linear %% sequencing of actions that are eventually run by an interpreter or the %% operating system. But in fact arrows are more general than monads, %% and in particular the composition of signal functions does not have to %% be completely linear, as will be illustrated shortly. \subsection{Four Useful Functions} \label{sec:useful-funs} There are four useful auxiliary functions that will make writing signal functions a bit easier. The first two essentially ``lift'' constants and functions from the Haskell level to the arrow (signal function) level: \begin{spec} arr :: Clock c => (a -> b) -> SigFun c a b constA :: Clock c => b -> SigFun c () b \end{spec} For example, a signal function that adds one to every sample of its input can be written simply as |arr (+1)|, and a signal function that returns the constant 440 as its result can be written |constA 440| (and is a signal source, as defined earlier). \out{ \begin{spec} constA :: Clock c => b -> SigFun c a b constA y = arr (\_ -> y) \end{spec} } The other two functions allow us to \emph{compose} signal functions: \begin{spec} (>>>) :: Clock clk => SigFun clk a b -> SigFun clk b c -> SigFun clk a c (<<<) :: Clock clk => SigFun clk b c -> SigFun clk a b -> SigFun clk a c \end{spec} |(<<<)| is analogous to Haskell's standard composition operator |(.)|, whereas |(>>>)| is like ``reverse composition.'' As an example that combines both of the ideas above, recall the very first example given in this chapter: \begin{spec} proc y -> do x <- sigfun -< y+1 outA -< x \end{spec} which essentially applies |sigfun| to one plus the input. This signal function can be written more succinctly as either |arr (+1) >>> sigfun| or |sigfun <<< arr (+1)|. The functions |(>>>)|, |(<<<)|, and |arr| are actually generic operators on arrows, and are defined in Haskell's |Arrow| library. Euterpea imports them from there and adds them to the Euterpea namespace, so they do not have to be explicitly imported by the user. \subsection{Some Simple Examples} \label{sec:sigfun-examples} Let's now work through a few examples that focus on the behavior of signal functions, so that we can get a feel for how they are used in practice. Euterpea has many pre-defined signal functions, including ones for sine waves, numeric computations, transcendental functions, delay lines, filtering, noise generation, integration, and so on. Many of these signal functions are inspired by csound \cite{csound}, where they are called \emph{unit generators}. Some of them are not signal functions \emph{per se}, but take a few fixed arguments to yield a signal function, and it is important to understand this distinction. For example, there are several pre-defined functions for generating sine waves and periodic waveforms in Euterpea. Collectively these are called \emph{oscillators}, a name taken from electronic circuit design. They are summarized in Figure \ref{fig:oscillators}. \begin{figure} \cbox{ \begin{spec} osc, oscI :: Clock c => Table -> Double -> SigFun c Double Double \end{spec} |osc tab ph| is a signal function whose input is a frequency, and output is a signal having that frequency. The output is generated using fixed-waveform table-lookup, using the table |tab|, starting with initial offset (phase angle) |ph| expressed as a fraction of a cycle (0 to 1). |oscI| is the same, but uses linear interpolation between points. \vspace{0.15in} \begin{spec} oscFixed :: Clock c => Double -> SigFun c () Double \end{spec} |oscFixed freq| is a signal source whose sinusoidal output frequency is |freq|. It uses a recurrence relation that requires only one multiply and two add operations for each sample of output. \vspace{0.15in} \begin{spec} oscDur, oscDurI :: Clock c => Table -> Double -> Double -> SigFun () Double \end{spec} |oscDur tab del dur| samples just once through the table |tab| at a rate determined by |dur|. For the first |del| seconds, the point of scan will reside at the first location of the table; it will then move through the table at a constant rate, reaching the end in another |dur| seconds; from that time on (i.e.\ after |del + dur| seconds) it will remain pointing at the last location. |oscDurI| is similar but uses linear interpolation between points. \vspace{0.15in} \begin{spec} oscPartials :: Clock c => Table -> Double -> SigFun c (Double,Int) Double \end{spec} |oscPartials tab ph| is a signal function whose pair of inputs determines the frequency (as with |osc|), as well as the number of harmonics of that frequency, of the output. |tab| is the table that is cycled through, and |ph| is the phase angle (as with |osc|). } \caption{Euterpea's Oscillators} \label{fig:oscillators} \end{figure} The two most common oscillators in Euterpea are: \begin{spec} osc :: Clock c => Table -> Double -> SigFun c Double Double oscFixed :: Clock c => Double -> SigFun c () Double \end{spec} |osc| uses fixed-waveform table-lookup synthesis as described in Section \ref{sec:wavetable}. The first argument is the fixed wavetable; we will see shortly how such a table can be generated. The second argument is the initial phase angle, represented as a fraction between 0 and 1. The resulting signal function then converts a signal representing the desired output frequency to a signal that has that output frequency. |oscFixed| uses an efficient recurrence relation to compute a pure sinusoidal wave; the mathematics of this are described in Section \ref{sec:sine-recurrence}. In contrast with |osc|, its single argument is the desired output frequency. The resulting signal function is therefore a signal source (i.e.\ its input type is |()|). \todo{Discuss recurrence relations here or perhaps in the last chapter where the fixed-waveform table-lookup method is described.} The key point here is that the frequency that is output by |osc| is an \emph{input to the signal function}, and therefore can vary with time, whereas the frequency output by |oscFixed| is a \emph{fixed argument}, and cannot vary with time. To see this concretely, let's define a signal source that generates a pure sine wave using |oscFixed| at a fixed frequency, say 440 Hz: \begin{code} s1 :: Clock c => SigFun c () Double s1 = proc () -> do s <- oscFixed 440 -< () outA -< s \end{code} Since the resulting signal |s| is directly returned through |outA|, this example can also be written: \begin{spec} s1 = proc () -> do oscFixed 440 -< () \end{spec} Alternatively, we could simply write |oscFixed 440|. To use |osc| instead, we first need to generate a wavetable that represents one full cycle of a sine wave. We can do this using one of Eutperpea's table generating functions, which are summarized in Figure~\ref{fig:table-generators}. For example, using Euterpea's |tableSinesN| function, we can define: \begin{code} tab1 :: Table tab1 = tableSinesN 4096 [1] \end{code} This will generate a table of 4096 elements, consisting of one sine wave whose peak amplitude is 1.0. Then we can define the following signal source: \begin{code} s2 :: Clock c => SigFun c () Double s2 = proc () -> do osc tab1 0 -< 440 \end{code} Alternatively, we could use the |const| and composition operators to write either |constA 440 >>> osc tab1 0| or |osc tab2 0 <<< constA 440|. |s1| and |s2| should be compared closely. \begin{figure} \cbox{\small \begin{spec} type TableSize = Int type PartialNum = Double type PartialStrength = Double type PhaseOffset = Double type StartPt = Double type SegLength = Double type EndPt = Double \end{spec} \vspace{0.05in} \begin{spec} tableLinear, tableLinearN :: TableSize -> StartPt -> [(SegLength, EndPt)] -> Table \end{spec} |tableLinear size sp pts| is a table of size |size| whose starting point is |(0,sp)| and that uses straight lines to move from that point to, successively, each of the points in |pts|, which are segment-length/endpoint pairs (segment lengths are projections along the x-axis). |tableLinearN| is a normalized version of the result. \vspace{0.15in} \begin{spec} tableExpon, tableExponN :: TableSize -> StartPt -> [(SegLength, EndPt)] -> Table \end{spec} Just like |tableLinear| and |tableLinearN|, respectively, except that exponential curves are used to connect the points. \vspace{0.15in} \begin{spec} tableSines3, tableSines3N :: TableSize -> [(PartialNum, PartialStrength, PhaseOffset)] -> Table \end{spec} |tableSines3 size triples| is a table of size |size| that represents a sinusoidal wave and an arbitrary number of partials, whose relationship to the fundamental frequency, amplitude, and phase are determined by each of the triples in |triples|. |tableSines3N| is a normalized version of the result. \vspace{0.15in} \begin{spec} tableSines, tableSinesN :: TableSize -> [PartialStrength] -> Table \end{spec} Like |tableSines3| and |tableSines3N|, respectively, except that the second argument is an ordered list of the strengths of each partial, starting with the fundamental. \vspace{0.15in} \begin{spec} tableBesselN :: TableSize -> Double -> Table \end{spec} |tableBesselN size x| is a table representing the log of a modified Bessel function of the second kind, order 0, suitable for use in amplitude-modulated FM. |x| is the x-interval (0 to |x|) over which the function is defined. } \caption{Table Generating Functions} \label{fig:table-generators} \end{figure} Keep in mind that |oscFixed| only generates a sine wave, whereas |osc| generates whatever is stored in the wavetable. Indeed, |tableSinesN| actually creates a table that is the sum of a series of overtones, i.e.\ multiples of the fundmental frequency (recall the discussion in Section~\ref{sec:spectrum}). For example: \begin{code} tab2 = tableSinesN 4096 [1.0,0.5,0.33] \end{code} generates a waveform consisting of the fundamental frequency with amplitude 1.0, the first overtone at amplitude 0.5, and the second overtone at amplitude 0.33. So a more complex sound can be synthesized just by changing the wavetable: \begin{code} s3 :: Clock c => SigFun c () Double s3 = proc () -> do osc tab2 0 -< 440 \end{code} To get the same effect using |oscFixed| we would have to write: \begin{code} s4 :: Clock c => SigFun c () Double s4 = proc () -> do f0 <- oscFixed 440 -< () f1 <- oscFixed 880 -< () f2 <- oscFixed 1320 -< () outA -< (f0 + 0.5*f1 + 0.33*f2) / 1.83 \end{code} Not only is this more complex, it is less efficient. (The division by 1.83 is to normalize the result---if the peaks of the three signals |f0|, |f1|, and |f2| align properly, the peak amplitude will be 1.83 (or -1.83), which is outside the range $\pm 1.0$ and may cause clipping (see discussion in Section~\ref{sec:generating-sound}). So far in these examples we have generated a signal whose fundamental frequency is 440 Hz. But as mentioned, in the case of |osc|, the input to the oscillator is a signal, and can therefore itself be time-varying. As an example of this idea, let's implement \emph{vibrato}---the performance effect whereby a musician slightly varies the frequency of a note in a pulsating rhythm. On a string instrument this is typically achieved by wiggling the finger on the fingerboard, on a reed instrument by an adjustment of the breath and emboucher to compress and relax the reed in a suitable way, and so on. Specifically, let's define a function: \begin{spec} vibrato :: Clock c => Double -> Double -> SigFun c Double Double \end{spec} such that |vibrato f d| is a signal function that takes a frequency argument (this is not a signal of a given frequency, it is the frequency itself), and generates a signal at that frequency, but with vibrato added, where |f| is the vibrato frequency, and |d| is the vibrato depth. We will consider ``depth'' to be a measure of how many Hz the input frequency is modulated. Intuitively, it seems as if we need \emph{two} oscillators, one to generate the fundamental frequency of interest, and the other to generate the vibrato (much lower in frequency). Here is a solution: \begin{code} vibrato :: Clock c => Double -> Double -> SigFun c Double Double vibrato vfrq dep = proc afrq -> do vib <- osc tab1 0 -< vfrq aud <- osc tab2 0 -< afrq + vib * dep outA -< aud \end{code} Note that a pure sine wave is used for the vibrato signal, whereas |tab2|, a sum of three sine waves, is chosen for the signal itself. For example, to play a 1000 Hz tone with a vibrato frequency of 5 Hz and a depth of 20 Hz, we could write: \begin{code} s5 :: AudSF () Double s5 = constA 1000 >>> vibrato 5 20 \end{code} Vibrato is actually an example of a more general sound synthesis technique called \emph{frequency modulation} (since one signal is being used to vary, or modulate, the frequency of another signal), and will be explained in more detail in Chapter~\ref{ch:fm}. Other chapters include synthesis techniques such as additive and subtractive synthesis, plucked instruments using waveguides, physical modeling, granular synthesis, as well as audio processing techniques such as filter design, reverb, and other effects. Now that we have a basic understanding of signal functions, these techniques will be straighforward to express in Euterpea. \section{Generating Sound} \label{sec:generating-sound} Euterpea can execute some programs in real-time, but sufficiently complex programs require writing the result to a file. The function for achieving this is: \begin{spec} outFile :: (AudioSample a, Clock c) => String -> Double -> SigFun c () a -> IO () \end{spec} %% outFile :: forall a p. (AudioSample a, Clock p) => %% String -- ^ Filename to write to. %% -> Double -- ^ Duration of the wav in seconds. %% -> SigFun p () a -- ^ Signal representing the sound. %% -> IO () The first argument is the name of the WAV file to which the result is written. The second argument is the duration of the result, in seconds (remember that signals are conceptually infinite). The third argument is a signal function that takes no input and generates a signal of type |a| as output (i.e.\ a signal source), where |a| is required to be an instance of the |AudioSample| type class, which allows one to choose between mono, stereo, etc. For convenience, Euterpea defines these type synonyms: \begin{spec} type Mono p = SigFun p () Double type Stereo p = SigFun p () (Double,Double) \end{spec} For example, the IO command |outfile "test.wav" 5 sf| generates 5 seconds of output from the signal function |sf|, and writes the result to the file |"test.wav"|. If |sf| has type |Mono AudRate| (i.e.\ |SigFun AudRate () Double| then the result will be monophonic; if the type is |Stereo AudRate| (i.e.\ |SigFun AudRate () (Double,Double)| the result will be stereophonic. %% |SigFun AudRate () (Double,Double,Double,Double)| yields %% quadraphonic sound, and so on. One might think that |outFile| should be restricted to |AudRate|. However, by allowing a signal of any clock rate to be written to a file, one can use external tools to analyze the result of control signals or other signals of interest as well. An important detail in writing WAV files with |outFile| is that care must be taken to ensure that each sample falls in the range $\pm 1.0$. If this range is exceeded, the output sound will be harshly distorted, a phenomenon known as \emph{clipping}. The reason that clipping sounds especially bad is that once the maximum limit is exceeded, the subsequent samples are interpreted as the \emph{negation} of their intended value---and thus the signal swings abruptly from its largest possible value to its smallest possible value. Of course, signals within your program may be well outside this range---it is only when you are ready to write the result to a file that clipping needs to be avoided. One can easily write signal functions that deal with clipping in one way or another. For example here's one that simply returns the maximum (positive) or mininum (negative) value if they are exceeded, thus avoiding the abrupt change in magnitude described above, and degenerating in the worst case to a square wave: \begin{code} simpleClip :: Clock c => SigFun c Double Double simpleClip = arr f where f x = if abs x <= 1.0 then x else signum x \end{code} \syn{|abs| is the absolute value function in Haskell, and |signum| returns -1 for negative numbers, 0 for zero, and 1 for positive numbers.} \todo{Define some signal functions to deal with time---for example one that ``takes'' the first |t| seconds of a signal function, returning zero for all times beyond that. We could write a special function to do this, but using Occam's Razor suppose we have a signal function |time :: Clock c => SigFun c () Double| that returns the current time. Then we could write: \begin{spec} takeSF :: Clock c => Double -> SigFun c Double Double takeSF t = proc x do now <- time -< () outA -< if now < t then x else 0 \end{spec} Indeed, time can be defined by: \begin{code} time :: Clock c => SigFun c () Double time = integral <<< constA 1 \end{code} Or, we could take a Yampa-like approach and use a ``switcher,'' but then we'd need some switcher signal functions. There is a collection-based switcher defined in |Euterpea.Audio.Render| called |pSwitch|, but we might want something simpler. Even with all this, it seems desirable to have a ``debug'' function that takes a time and a signal function, and returns a Boolean indicating whether or not the signal function clipped or not during that period of time. Again using Occam's razor, it seems best to define a function |sfToList| that returns the infinite list underlying a signal source. If we know the clock rate, then ``take''ing a suitable prefix of this list will return the desired result. Then, for example, |max (take 44100 (sfToList ss))| yields the maximum value of the first 44100 samples of the signal source |ss|. One could then use this to normalize the |ss|. Note that |sfToList| is not something that can be defined using Euterpea as a library---it would have to be defined within Euterpea's implementation of signal functions. } \section{Instruments} \label{sec:euterp-instruments} So far we have only considered signal functions as stand-alone values whose output we can write to a WAV file. But how do we connect the ideas in previous chapters about |Music| values, |Performance|s, and so on, to the ideas presented in this chapter? This section presents a bridge between the two worlds. \subsection{Turning a Signal Function into an Instrument} Suppose that we have a |Music| value that, previously, we would have played using a MIDI instrument, and now we want to play using an instrument that we have designed using signal functions. To do this, first recall from Chapter~\ref{ch:music} that the |InstrumentName| data type has a special constructor called |Custom|: \begin{spec} data InstrumentName = AcousticGrandPiano | BrightAcousticPiano | ... | Custom String deriving (Show, Eq, Ord) \end{spec} With this constructor, names (represented as strings) can be given to instruments that we have designed using signal functions. For example: \begin{code} simpleInstr :: InstrumentName simpleInstr = Custom "Simple Instrument" \end{code} Now we need to define the instrument itself. Euterpea defines the following type synonym: \begin{spec} type Instr a = Dur -> AbsPitch -> Volume -> [Double] -> a \end{spec} Although |Instr| is polymorphic, by far its most common instantiation is the type |Instr (AufSF () Double)|. An instrument of this type is a function that takes a duration, absolute pitch, volume, and a list of parameters, and returns a signal source that generates the resulting sound. The list of parameters (similar to the ``pfields'' in csound) are not used by MIDI instruments, and thus have not been discussed until now. They afford us unlimited expressiveness in controlling the sound of our signal-function based instruments. Recall from Chapter~\ref{ch:performance} the types: \begin{spec} type Music1 = Music Note1 type Note1 = (Pitch, [NoteAttribute]) data NoteAttribute = Volume Int | Fingering Integer | Dynamics String | Params [Double] deriving (Eq, Show) \end{spec} Using the |Params| constructor, each individual note in a |Music1| value can be given a different list of parameters. It is up to the instrument designer to decide how these parameters are used. There are three steps to playing a |Music| value using a user-defined instrument. First, we must coerce our signal function into an instrument having the proper type |Instr| as described above. For example, let's turn the |vibrato| function from the last section into a (rather primitive) instrument: \begin{code} myInstr :: Instr (AudSF () Double) -- |Dur -> AbsPitch -> Volume -> [Double] -> (AudSF () Double)| myInstr dur ap vol [vfrq,dep] = proc () -> do vib <- osc tab1 0 -< vfrq aud <- osc tab2 0 -< apToHz ap + vib * dep outA -< aud \end{code} Aside from the re-shuffling of arguments, note the use of the function |apToHz|, which converts an absolute pitch into its corresponding frequency: \begin{spec} apToHz :: Floating a => AbsPitch -> a \end{spec} Next, we must connect our instrument name (used in the |Music| value) to the instrument itself (such as defined above). This is achieved using a simple association list, or \emph{instrument map}: \begin{spec} type InstrMap a = [(InstrumentName, Instr a)] \end{spec} Continuing the example started above: \begin{code} myInstrMap :: InstrMap (AudSF () Double) myInstrMap = [(simpleInstr, myInstr)] \end{code} Finally, we need a function that is analogous to |perform| from Chapter~\ref{ch:performance}, except that instead of generating a |Performance|, it creates a single signal function that will ``play'' our |Music| value for us. In Euterpea that function is called |renderSF|: \begin{spec} renderSF :: (Performable a, AudioSample b, Clock c) => Music a -> InstrMap (SigFun p () b) -> (Double, SigFun p () b) \end{spec} The first element of the pair that is returned is the duration of the |Music| value, just as is returned by |perform|. That way we know how much of the signal function to render in order to hear the entire composition. Using the simple melody |mel| in Figure~\ref{fig:reflections}, and the simple vibrato instrument defined above, we can generate our result and write it to a file, as follows: \begin{code} (dr, sf) = renderSF mel myInstrMap main = outFile "simple.wav" dr sf \end{code} For clarity we show in Figure~\ref{fig:sf-instrument} all of the pieces of this running example as one program. \begin{figure} \cbox{ \begin{code} mel :: Music1 mel = let m = Euterpea.line [ na1 (c 4 en), na1 (ef 4 en), na1 (f 4 en), na2 (af 4 qn), na1 (f 4 en), na1 (af 4 en), na2 (bf 4 qn), na1 (af 4 en), na1 (bf 4 en), na1 (c 5 en), na1 (ef 5 en), na1 (f 5 en), na3 (af 5 wn) ] na1 (Prim (Note d p)) = Prim (Note d (p,[Params [0, 0]])) na2 (Prim (Note d p)) = Prim (Note d (p,[Params [5,10]])) na3 (Prim (Note d p)) = Prim (Note d (p,[Params [5,20]])) in instrument simpleInstr m \end{code}} \caption{A Simple Melody} \label{fig:reflections} \end{figure} \begin{figure} \cbox{ \begin{spec} simpleInstr :: InstrumentName simpleInstr = Custom "Simple Instrument" myInstr :: Instr (AudSF () Double) myInstr dur ap vol [vfrq,dep] = proc () -> do vib <- osc tab1 0 -< vfrq aud <- osc tab2 0 -< apToHz ap + vib * dep outA -< aud myInstrMap :: InstrMap (AudSF () Double) myInstrMap = [(simpleInstr, myInstr)] (d, sf) = renderSF mel myInstrMap main = outFile "simple.wav" d sf \end{spec}} \caption{A Complete Example of a Signal-Function Based Instrument} \label{fig:sf-instrument} \end{figure} \subsection{Envelopes} \label{sec:envelopes} Most instruments played by humans have a distinctive sound that is partially dependent on how the performer plays a particular note. For example, when a wind instrument is played (whether it be a flute, saxophone, or trumpet), the note does not begin instantaneously---it depends on how quickly and forcibly the performer blows into the instrument. This is called the ``attack.'' Indeed, it is not uncommon for the initial pulse of energy to generate a sound that is louder than the ``sustained'' portion of the sound. And when the note ends, the airflow does not stop instantaneously, so there is variability in the ``release'' of the note. The overall variability in the loudness of a note can be simulated by multiplying the output of a signal function by an \emph{envelope}, which is a time-varying signal that captures the desired behavior. Indeed, the \emph{ADSR envelope} (attack, decay, sustain, release) introduced above is one of the most common envelopes used in practice. It is shown pictorially in Figure \ref{fig:ADSR}. Before defining it in Euterpea, however, we first describe a collection of simpler envelopes. \begin{figure} ... \caption{ADSR Envelope} \label{fig:ADSR} \end{figure} Figure~\ref{fig:line-envelopes} shows six pre-defined envelope-generating functions. Read the code comments carefully to understand what they do. \begin{figure} \cbox{\small \begin{spec} -- a linear envelope envLine :: Clock p => Double -> -- starting value Double -> -- duration in seconds Double -> -- value after dur seconds SigFun p () Double -- an exponential envelope envExpon :: Clock p => Double -> -- starting value; zero is illegal for exponentials Double -> -- duration in seconds Double -> -- value after dur seconds (must be non-zero -- and agree in sign with first argument) SigFun p () Double -- a series of linear envelopes envLineSeg :: Clock p => [Double] -> -- list of points to trace through [Double] -> -- list of durations for each line segment -- (one element fewer than previous argument) SigFun p () Double -- a series of exponential envelopes envExponSeg :: Clock p => [Double] -> -- list of points to trace through [Double] -> -- list of durations for each line segment -- (one element fewer than previous argument) SigFun p () Double -- an ``attack/decay/release'' envelope; each segment is linear envASR :: Clock p => Double -> -- rise time in seconds Double -> -- overall duration in seconds Double -> -- decay time in seconds SigFun p () Double -- a more sophisticated ASR envCSEnvlpx :: Clock p => Double -> -- rise time in seconds Double -> -- overall duration in seconds Double -> -- decay time in seconds Table -> -- table representing rise shape Double -> -- attenuation factor, by which the last value -- of the envlpx rise is modified during the -- note's pseudo steady state Double -> -- attenuation factor by which the closing -- steady state value is reduced exponentially -- over the decay period SigFun p () Double \end{spec}} \caption{Envelopes} \label{fig:line-envelopes} \end{figure} Here are some additional comments regarding |envCSEnvplx|, easily the most sophisticated of the envelope generators: \begin{enumerate} \item The fifth argument to |envCSEnvplx|: A value greater than 1 causes exponential growth; a value less than 1 causes exponential decay; a value = 1 will maintain a true steady state at the last rise value. The attenuation is not by a fixed rate (as in a piano), but is sensitive to a note's duration. However, if this argument is less than 0 (or if steady state is less than 4 k-periods) a fixed attenuation rate of |abs atss| per second is used. A value of 0 is illegal. \item The sixth arg to |envCSEnvplx|: Must be positive and is normally of the order of 0.01. A large or excessively small value is apt to produce a cutoff that is not audible. Values less than or equal to 0 are disallowed. \end{enumerate} \vspace{.1in}\hrule \begin{exercise}{\em Using the Euterpea function |osc|, create a simple sinusoidal wave, but using different table sizes, and different frequencies, and see if you can hear the differences (report on what you hear). Use |outFile| to write your results to a file, and be sure to use a decent set of speakers or headphones.} \end{exercise} \begin{exercise}{\em The |vibrato| function varies a signal’s frequency at a given rate and depth. Define an analogous function |tremolo| that varies the volume at a given rate and depth. However, in a sense, |tremolo| is a kind of envelope (infinite in duration), so define it as a signal source, with which you can then shape whatever signal you wish. Consider the ``depth'' to be the fractional change to the volume; that is, a value of 0 would result in no tremolo, a value of 0.1 would vary the amplitude from 0.9 to 1.1, and so on. Test your result.} \label{ex:tremolo} \end{exercise} \begin{exercise}{\em Define an ADSR (``attack/decay/sustain/release'') envelope generator (i.e. a signal source) called |envADSR|, with type: \begin{spec} type DPair = (Double, Double) -- pair of duration and amplitude envADSR :: DPair -> DPair -> DPair -> Double -> AudSF () Double \end{spec} The three |DPair| arguments are the duration and amplitude of the attack, decay, and release ``phases,'' respectively, of the envelope. The sustain phase should hold the last value of the decay phase. The fourth argument is the duration of the entire envelope, and thus the duration of the sustain phase should be that value minus the sum of the durations of the other three phases. (Hint: use Euterpea’s |envLineSeg| function.) Test your result. } \end{exercise} \begin{exercise}{\em Generate a signal that causes clipping, and listen to the result. Then use |simpleClip| to ``clean it up'' somewhat---can you hear the difference? Now write a more ambitious clipping function. In particular, one that uses some kind of non-linear reduction in the signal amplitude as it approaches plus or minus one (rather than abruptly ``sticking'' at plus or minus one, as in |simpleClip|).} \end{exercise} \begin{exercise}{\em Define two instruments, each of type |Instr (AudSF () Double)|. These can be as simple as you like, but each must take at least two |Params|. Define an |InstrMap| that uses these, and then use |renderSF| to ``drive'' your instruments from a |Music1| value. Test your result.} \end{exercise} \vspace{.1in}\hrule