temporal-music-notation-0.4.1: music notation

Safe HaskellNone
LanguageHaskell98

Temporal.Music.Score

Contents

Description

Composition and control.

Synopsis

Types

type Dur = Double Source

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 a Source

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

rest :: Dur -> Score a Source

Empty Score that lasts for some time.

str :: Dur -> Score a -> Score a Source

Stretches Score in time domain.

del :: Dur -> Score a -> Score a Source

Delays all events by given duration.

reflect :: Score a -> Score a Source

Reversing the scores

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

Infix del function.

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

Infix str function.

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

Parallel composition. Play two scores simultaneously.

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

Sequent composition. Play first score then second.

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

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

mel :: [Score a] -> Score a Source

Sequent composition on list of scores.

har :: [Score a] -> Score a Source

Parallel composition on list of scores.

harT :: [Score a] -> Score a Source

Turncating parallel composition on list of scores.

loop :: Int -> Score a -> Score a Source

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

sustain :: Dur -> Score a -> Score a Source

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

sustainT :: Dur -> Score a -> Score a Source

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

melTemp :: [a] -> Score a Source

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

harTemp :: [a] -> Score a Source

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

melMap :: (a -> Score b) -> [a] -> Score b Source

Transforms a sequence and then applies a mel.

harMap :: (a -> Score b) -> [a] -> Score b Source

Transforms a sequence and then applies a har.

harTMap :: (a -> Score b) -> [a] -> Score b Source

Transforms a sequence and then applies a harT.

Filtering

slice :: Dur -> Dur -> Score a -> Score a Source

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 a Source

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

dropS :: Dur -> Score a -> Score a Source

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

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

Filter score.

Mappings

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

General mapping. Mapps not only values but events.

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

Mapps values and time stamps.

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

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

Rendering

dur :: Score a -> Dur Source

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 a Source

Sets diapason to specified value.

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

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

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

Sets level to the given value.

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

Sets accent to the given value

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

Increases Accent by the given value.

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

Synonym for flip setAcent

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

Input becomes louder by given number of levels.

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

Input becomes quieter by given number of levels.

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

Input becomes one level louder.

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

Input becomes one level quieter.

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

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 a Source

envelopeSeg lifts function linfun to dynamics level

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

envelopeRel lifts function linfunRel to dynamics level

Pitch control

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

Sets new scale

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

Sets bend value

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

Sets step value

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

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

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

Increases Bend by given value.

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

Transposition by given number of octaves.

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

Transposition by given number of octaves.

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

One octave lower.

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

One octave higher.

Shortcuts

Denotes lower 1-2 and higher 1-2.

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

ll' :: PitchLike a => Score a -> Score a Source

hh' :: PitchLike a => Score a -> Score a Source

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

Time stretching

r :: Dur -> Score a Source

Shortcut for rest

dot :: Score a -> Score a Source

Synonym to str (3/2)

ddot :: Score a -> Score a Source

double dot, str with 1.75

trn :: Score a -> Score a Source

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

bpm :: Dur -> Score a -> Score a Source

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 (str 2)

w means whole (str 1)

h means half (str $ 1/2)

q means quater (str $ 1/4)

e means eighth (str $ 1/8)

s means sixteenth (str $ 1/16)

t means thirty second (str $ 1/32)

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

bn :: Score a -> Score a Source

wn :: Score a -> Score a Source

hn :: Score a -> Score a Source

qn :: Score a -> Score a Source

en :: Score a -> Score a Source

sn :: Score a -> Score a Source

tn :: Score a -> Score a Source

dbn :: Score a -> Score a Source

dwn :: Score a -> Score a Source

dhn :: Score a -> Score a Source

dqn :: Score a -> Score a Source

den :: Score a -> Score a Source

dsn :: Score a -> Score a Source

dtn :: Score a -> Score a Source

Pauses

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

Deprecated

line :: [Score a] -> Score a Source

Deprecated: Use mel

Deprecated in favour of mel.

chord :: [Score a] -> Score a Source

Deprecated: Use har

Deprecated in favour of har.

delay :: Double -> Score a -> Score a Source

Deprecated: Use del

Deprecated in favour of del.

stretch :: Double -> Score a -> Score a Source

Deprecated: Use str

Deprecated in favour of str.