temporal-music-notation-0.2.3: music notation

Safe HaskellNone

Temporal.Music.Score

Contents

Description

Composition and control.

Synopsis

Types

type Dur = DoubleSource

Duration.

data Event t a

Constant time events. Value a starts at some time and lasts for some time.

Constructors

Event 

Fields

eventStart :: t
 
eventDur :: t
 
eventContent :: a
 

Instances

Functor (Event t) 
(Eq t, Eq a) => Eq (Event t a) 
(Show t, Show a) => Show (Event t a) 

eventEnd :: Num t => Event t a -> t

End point of event (start time plus duration).

within :: Real t => t -> t -> Event t a -> Bool

Tests if given Event happens between two time stamps.

Composition

temp :: a -> Score aSource

temp constructs just an event. Value of type a lasts for one time unit and starts at zero.

event :: Dur -> a -> Score aSource

Creates a single event.

 event dur a 

Event lasts for some time and contains a value a.

rest :: Dur -> Score aSource

Empty Score that lasts for some time.

stretch :: Dur -> Score a -> Score aSource

Stretches Score in time domain.

delay :: Dur -> Score a -> Score aSource

Delays all events by given duration.

reflect :: Score a -> Score aSource

Reversing the scores

(+|) :: Dur -> Score a -> Score aSource

Infix delay function.

(*|) :: Dur -> Score a -> Score aSource

Infix stretch function.

(=:=) :: Score a -> Score a -> Score aSource

Parallel composition. Play two scores simultaneously.

(+:+) :: Score a -> Score a -> Score aSource

Sequent composition. Play first score then second.

(=:/) :: Score a -> Score a -> Score aSource

Turncating parallel composition. Total duration equals to minimum of the two scores. All events that goes beyond the lmimt are dropped.

line :: [Score a] -> Score aSource

Sequent composition on list of scores.

chord :: [Score a] -> Score aSource

Parallel composition on list of scores.

chordT :: [Score a] -> Score aSource

Turncating parallel composition on list of scores.

loop :: Int -> Score a -> Score aSource

Analog of replicate function for scores. Replicated scores are played sequentially.

sustain :: Dur -> Score a -> Score aSource

After this transformation events last longer by some constant amount of time.

sustainT :: Dur -> Score a -> Score aSource

Prolongated events can not exceed total score duration. All event are sustained but those that are close to end of the score are clipped. It resembles sustain on piano, when score ends you release the pedal.

Common patterns

lineTemp :: [a] -> Score aSource

A line of one events. Each of them lasts for one second.

chordTemp :: [a] -> Score aSource

A chord of one events. Each of them lasts for one second.

lineMap :: (a -> Score b) -> [a] -> Score bSource

Transforms a sequence and then applies a line.

chordMap :: (a -> Score b) -> [a] -> Score bSource

Transforms a sequence and then applies a chord.

chordTMap :: (a -> Score b) -> [a] -> Score bSource

Transforms a sequence and then applies a chordT.

Filtering

slice :: Dur -> Dur -> Score a -> Score aSource

slice cuts piece of value within given time interval. for (slice t0 t1 m), if t1 < t0 result is reversed. If t0 is negative or t1 goes beyond dur m blocks of nothing inserted so that duration of result equals to abs (t0 - t1).

takeS :: Dur -> Score a -> Score aSource

(takeS t) is equivalent to (slice 0 t).

dropS :: Dur -> Score a -> Score aSource

(dropS t m) is equivalent to (slice t (dur a) a).

filterEvents :: (Event Dur a -> Bool) -> Score a -> Score aSource

Filter score.

Mappings

mapEvents :: (Event Dur a -> Event Dur b) -> Score a -> Score bSource

General mapping. Mapps not only values but events.

tmap :: (Event Dur a -> b) -> Score a -> Score bSource

Mapps values and time stamps.

tmapRel :: (Event Dur a -> b) -> Score a -> Score bSource

Relative tmap. Time values are normalized by argument's duration.

Rendering

dur :: Score a -> DurSource

Calculates duration.

render :: Score a -> [Event Dur a]Source

Gets all recordered events.

alignByZero :: Real t => [Event t a] -> [Event t a]

Shifts all events so that minimal start time equals to zero if first event has negative start time.

sortEvents :: Ord t => [Event t a] -> [Event t a]

Sorts all events by start time.

Miscellaneous

linfun :: (Ord t, Fractional t) => [t] -> t -> t

Linear interpolation. Can be useful with mapEvents for envelope changes.

 linfun [a, da, b, db, c, ... ]

a, b, c ... - values

da, db, ... - duration of segments

linfunRel :: (Ord t, Fractional t) => t -> [t] -> t -> t

With linfunRel you can make linear interpolation function that has equal distance between points. First argument gives total length of the interpolation function and second argument gives list of values. So call

 linfunRel dur [a1, a2, a3, ..., aN]

is equivalent to:

 linfun [a1, dur/N, a2, dur/N, a3, ..., dur/N, aN]

Monoid synonyms

This package heavily relies on Monoids, so there are shorcuts for Monoid methods.

nil :: Monoid a => a

Synonym for method mempty.

Volume control

setDiap :: VolumeLike a => (Double, Double) -> Score a -> Score aSource

Sets diapason to specified value.

setDiapRel :: VolumeLike a => (Double, Double) -> Score a -> Score aSource

Relative update of diapason value in decibels, (0, 1) turns diapason interval into itself.

setLevel :: VolumeLike a => Level -> Score a -> Score aSource

Sets level to the given value.

setAccent :: VolumeLike a => Accent -> Score a -> Score aSource

Sets accent to the given value

accent :: VolumeLike a => Accent -> Score a -> Score aSource

Increases Accent by the given value.

(!) :: VolumeLike a => Score a -> Accent -> Score aSource

Synonym for flip setAcent

louder :: VolumeLike a => Int -> Score a -> Score aSource

Input becomes louder by given number of levels.

quieter :: VolumeLike a => Int -> Score a -> Score aSource

Input becomes quieter by given number of levels.

loud :: VolumeLike a => Score a -> Score aSource

Input becomes one level louder.

quiet :: VolumeLike a => Score a -> Score aSource

Input becomes one level quieter.

withAccent :: VolumeLike a => (Dur -> Accent) -> Score a -> Score aSource

Accent that depends on time of note, time is relative, so Score starts at 't = 0' and ends at 't = 1'.

withAccentSeg :: VolumeLike a => [Double] -> Score a -> Score aSource

envelopeSeg lifts function linfun to dynamics level

withAccentRel :: VolumeLike a => [Accent] -> Score a -> Score aSource

envelopeRel lifts function linfunRel to dynamics level

Pitch control

setScale :: PitchLike a => Scale -> Score a -> Score aSource

Sets new scale

setBend :: PitchLike a => Bend -> Score a -> Score aSource

Sets bend value

setStep :: PitchLike a => Step -> Score a -> Score aSource

Sets step value

step :: PitchLike a => Int -> Score a -> Score aSource

Transposition. Increases (octave, step) coordinate by given number of steps.

bend :: PitchLike a => Bend -> Score a -> Score aSource

Increases Bend by given value.

lower :: PitchLike a => Int -> Score a -> Score aSource

Transposition by given number of octaves.

higher :: PitchLike a => Int -> Score a -> Score aSource

Transposition by given number of octaves.

low :: PitchLike a => Score a -> Score aSource

One octave lower.

high :: PitchLike a => Score a -> Score aSource

One octave higher.

Shortcuts

Denotes lower 1-2 and higher 1-2.

l' :: PitchLike a => Score a -> Score aSource

h' :: PitchLike a => Score a -> Score aSource

Time stretching

r :: Dur -> Score aSource

Shortcut for rest

dot :: Score a -> Score aSource

Synonym to stretch (3/2)

ddot :: Score a -> Score aSource

double dot, stretch with 1.75

trn :: Score a -> Score aSource

Means 'three notes'. Plays three notes as fast as two.

bpm :: Dur -> Score a -> Score aSource

Sets tempo in beats per minute, if 1 Dur is equal to 1 second before transformation.

Shortcuts

Naming conventions :

First part x can be [b | w | h | q | e | s | t | d[x] ]

b means brewis (stretch 2)

w means whole (stretch 1)

h means half (stretch $ 1/2)

q means quater (stretch $ 1/4)

e means eighth (stretch $ 1/8)

s means sixteenth (stretch $ 1/16)

t means thirty second (stretch $ 1/32)

d[x] means dotted [x] (stretch 1.5 $ x)

bn :: Score a -> Score aSource

wn :: Score a -> Score aSource

hn :: Score a -> Score aSource

qn :: Score a -> Score aSource

en :: Score a -> Score aSource

sn :: Score a -> Score aSource

tn :: Score a -> Score aSource

Pauses

Naming conventions are the same as for 'time stretching'.