music-score-1.9.0: Musical score and part representation.

Copyright(c) Hans Hoglund 2012-2014
LicenseBSD-style
Maintainerhans@hanshoglund.se
Stabilityexperimental
Portabilitynon-portable (TF,GNTD)
Safe HaskellNone
LanguageHaskell2010

Music.Time.Types

Contents

Description

 

Synopsis

Basic types

data Time Source

Time represents points in time space. The difference between two time points is a Duration, for example in a bar of duration 4/4 (that is 1), the difference between the first and third beat 1/2.

Time has an origin (zero) which usually represents the beginning of the musical performance, but this may not always be the case, as the modelled music may be infinite, or contain a musical pickup. Hence Time values can be negative.

data Duration Source

Duration, corresponding to note values in standard notation. The standard names can be used: 1/2 for half note 1/4 for a quarter note and so on.

type LocalDuration = Alignment Source

Deprecated: Use Alignment

Convert between time and duration

Note that you should use .-. and .+^ to convert between time and duration. To refer to time zero (the beginning of the music), use origin.

toAbsoluteTime :: [Duration] -> [Time] Source

Interpret as durations from 0.

toAbsoluteTime (toRelativeTime xs) == xs
lenght xs == length (toRelativeTime xs)
>>> toAbsoluteTime [1,1,1] :: [Time]
[1,2,3]

toRelativeTime :: [Time] -> [Duration] Source

Duration between 0 and first value and so on until the last.

toAbsoluteTime (toRelativeTime xs) == xs
lenght xs == length (toRelativeTime xs)
>>> toRelativeTime [1,2,3]
[1,1,1]

toRelativeTimeN' :: Time -> [Time] -> [Duration] Source

Duration between values until the last, then up to the given final value. > lenght xs == length (toRelativeTime xs)

Time spans

data Span Source

A Span represents a specific time interval, such as the duration of a note, phrase or musical piece. It can be modelled as two points, or as a point and a vector.

Another way of looking at Span is that it represents a time transformation where onset is translation and duration is scaling.

This type is known as Arc in Tidal and as Era in the active package.

Constructing spans

(<->) :: Time -> Time -> Span infixl 6 Source

t <-> u represents the span between t and u.

(>->) :: Time -> Duration -> Span infixl 6 Source

t >-> d represents the span between t and t .+^ d.

(<-<) :: Duration -> Time -> Span infixl 6 Source

d <-> t represents the span between t .-^ d and t.

delta :: Iso' Span (Time, Duration) Source

View a span as a pair of onset and duration.

range :: Iso' Span (Time, Time) Source

View a span as pair of onset and offset.

codelta :: Iso' Span (Duration, Time) Source

View a span as a pair of duration and offset.

stretchComponent :: Span -> Duration Source

Access the stretch component in a span.

delayComponent :: Span -> Time Source

Access the delay component in a span.

fixedDurationSpan :: Prism' Span Time Source

A prism to the subset of Span that performs a delay but no stretch.

fixedOnsetSpan :: Prism' Span Duration Source

A prism to the subset of Span that performs a stretch but no delay.

Transformations

normalizeSpan :: Span -> Span Source

Normalize a span, i.e. reverse it if negative, and do nothing otherwise.

abs $ s^.duration = abs $ (normalizeSpan s)^.duration
s^.midpoint = (normalizeSpan s)^.midpoint

reverseSpan :: Span -> Span Source

Reflect a span through its midpoint.

reflectSpan :: Time -> Span -> Span Source

Reflect a span through an arbitrary point.

Properties

isEmptySpan :: Span -> Bool Source

Whether the given span is empty, i.e. whether its onset and offset are equivalent.

isForwardSpan :: Span -> Bool Source

Whether the given span has a positive duration, i.e. whether its onset is before its offset.

isBackwardSpan :: Span -> Bool Source

Whether the given span has a negative duration, i.e. whether its offset is before its onset.

Points in spans

inside :: Time -> Span -> Bool infixl 5 Source

Whether the given point falls inside the given span (inclusively).

Designed to be used infix, for example

>>> 0.5 `inside` 1 <-> 2
False
>>> 1.5 `inside` 1 <-> 2
True
>>> 1 `inside` 1 <-> 2
True

Partial orders

encloses :: Span -> Span -> Bool infixl 5 Source

Whether the first given span encloses the second span.

>>> 0 <-> 3 `encloses` 1 <-> 2
True
>>> 0 <-> 2 `encloses` 1 <-> 2
True
>>> 1 <-> 3 `encloses` 1 <-> 2
True
>>> 1 <-> 2 `encloses` 1 <-> 2
True

properlyEncloses :: Span -> Span -> Bool infixl 5 Source

Whether the first given span encloses the second span.

>>> 0 <-> 3 `properlyEncloses` 1 <-> 2
True
>>> 0 <-> 2 `properlyEncloses` 1 <-> 2
True
>>> 1 <-> 3 `properlyEncloses` 1 <-> 2
True
>>> 1 <-> 2 `properlyEncloses` 1 <-> 2
False

overlaps :: Span -> Span -> Bool infixl 5 Source

Whether the given span overlaps.

etc.

isBefore :: Span -> Span -> Bool Source

Whether the first given span occurs before the second span.

Read/Show

showRange :: Span -> String Source

Show a span in range notation, i.e. t1 <-> t2.

showDelta :: Span -> String Source

Show a span in delta notation, i.e. t >-> d.

showCodelta :: Span -> String Source

Show a span in codelta notation, i.e. t <-< d.