csound-expression-0.1.0: Csound combinator library

CsoundExpr.Tutorial.Composition

Contents

Description

Module CsoundExpr.Base.Score provides functions to construct csound's score section

Synopsis

EventList

EventList contains values with time marks. Value begins at some time and lasts for some time (see temporal-media package) EventList can be constructed from Score with toList function.

Score

Score is tree structure that represents music. Lists contain notes and nodes contain information about how subtrees relate to each other in time. Subtrees can be sequential or parallel. csd function takes in EventList Double SignalOut. Double is type of time-marks. SignalOut represents instrument structure.

Score's instances

Score is a Functor, Monad, Temporal, Stretchable, Arrangeable and TemporalFunctor

Functor

It makes possible to represent csound's instrument as a function from note representation to SignalOut.

To play on instrument means to apply instrument to Score of its notes.

-- oscillator instrument
instr :: Irate -> SignalOut
instr x = out $ oscilA [] (num 1000) (cpspch x) $ gen10 4096 [1]

exmpScoFunctor = fmap instr $ line $ map (note 1) [d 0, f 0, a 0, d 1]

Monad

Gives way to more structured composition.

return a makes note of a that lasts for 1 sec. ma >>= f is better understood by its join function.

ma >>= f = joinScore $ fmap f ma

joinScore :: Score (Score a) -> Score a

Score a is a tree. Nodes represent sequent/parallel composition and leaves represent value a or rest that lasts for some time t. joinScore takes in Score that contains some more Score 's in its leaves, and builds one tree by substituting values of Scores by Scores. Note that while substituting it stretches duration of Score by duration of value.

type ChordType = [Irate]

majC, minC :: ChordType

majC = [0, 0.04, 0.07]  -- in csound 0.01 is one half-tone
minC = [0, 0.03, 0.07]

arpeggi :: (Irate, ChordType) -> Score Irate
arpeggi baseNote chordType = line $ map return (pchs ++ pchs)
   where pchs = map ((+ baseNote) . (chordType !! )) [0, 1, 2, 1, 2, 1]    

harmony = line $ map return 
    [(e 0, minC), (a (-1), minC), (d 0, majC),    (g 0, majC),
     (c 0, majC), (f 0, minC),    (b (-1), majC), (e 0, minC)]

sco = harmony >>= arpeggi

Temporal

There are two methods defined on Temporal objects.

none :: Dur -> a  -- construct rest
dur  :: a -> Dur  -- ask for duration

Stretchable

Stretching things in time domain with stretch method.

 stretch :: Dur -> a -> a

Arrangeable

Constructing things in sequent '(+:+)' and parallel ways '(=:=)'

TemporalFunctor

There is class called TemporalFunctor with method tmap. First argument of tmap's function means function from duration of value t and value itself a to new value b.

class Dur t => TemporalFunctor f where
    tmap :: (t -> a -> b) -> f a -> f b

It allows to construct instruments that can rely on note duration.

instr :: Dur -> Irate -> SignalOut
instr t vol = out $ (env t <*> ) $ fst $ se1 $ unirandA vol
   where env t
           | t < 1     = lineK  1 idur 0
           | otherwise = exponK 1 idur 0

v1 = 1.5 * v0
v0 = 5000

sco = tmap instr $ line [note 0.5 v1, note 0.5 v0, rest 1, note 2 v1]

Note :

stretch t (tmap instr sco) =/= tmap instr (stretch t sco)

Example

radiohead - weird fishes (intro), see src