music-score-1.7.2: 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

Time points

data Time Source

Time points, representing duration since some known reference time, typically the start of the music. Note that time can be negative, representing values occuring before the reference time.

Time forms an affine space with durations as the underlying vector space, that is, we can add a time to a duration to get a new time using .+^, take the difference of two times to get a duration using .-.. Time forms an AffineSpace with Duration as difference space.

toTime :: Real a => a -> Time Source

Convert a value to a duration.

fromTime :: Fractional a => Time -> a Source

Convert a value to a duration.

Duration

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.

Duration is a one-dimensional VectorSpace, and is the associated vector space of time points. It is a also an AdditiveGroup (and hence also Monoid and Semigroup) under addition.

Duration is invariant under translation so delay has no effect on it.

toDuration :: Real a => a -> Duration Source

Convert a value to a duration.

fromDuration :: Fractional a => Duration -> a Source

Convert a value to a duration.

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.

offsetPoints :: AffineSpace a => a -> [Diff a] -> [a] Source

length (offsetPoints x xs) = length xs + 1
>>> offsetPoints (0 ::Double) [1,2,1]
[0.0,1.0,3.0,4.0]
offsetPoints :: AffineSpace a => Time -> [Duration] -> [Time]

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

Convert from delta (time to wait before this note)

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

Convert to delta (time to wait before this note)

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

Convert to delta (time to wait before next note)

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

Convert to delta (time to wait before next note)

Time spans

data Span Source

A Span represents an onset and offset in time (or equivalently: an onset and a duration, or a duration and an offset, or a duration and a middle point).

Pattern matching over span is possible (with ViewPatterns):

foo (view range   -> (t1, t2)) = ...
foo (view delta   -> (t1, d))  = ...
foo (view codelta -> (d,  t2)) = ...

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

TODO How to use with transform, whilst etc.

a <-> b = (a, b)^.from range
a >-> b = (a, b)^.from delta
a <-< b = (a, b)^.from codelta

Instances

Eq Span 
Ord Span 
Show Span 
ToJSON Span 
Monoid Span

<> or ^+^ composes transformations, i.e. both time and duration is stretched, and then time is added.

Semigroup Span

zeroV or mempty represents the unit interval 0 <-> 1, which also happens to be the identity transformation.

AdditiveGroup Span

negateV returns the inverse of a given transformation.

Transformable Span 
HasDuration Span 
HasPosition Span 
Splittable Span 
Reversible Span 
Typeable * Span 

Creating 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.

Accessing spans

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

View a span as pair of onset and offset.

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

View a span as a pair of onset and duration.

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

View a span as a pair of duration and offset.

Properties

A span is either forward, backward or empty.

any id [isForwardSpan x, isBackwardSpan x, isEmptySpan x] == True all not [isForwardSpan x, isBackwardSpan x, isEmptySpan x] == False

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.

isEmptySpan :: Span -> Bool Source

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

Transformations

reverseSpan :: Span -> Span Source

Reflect a span through its midpoint.

reflectSpan :: Time -> Span -> Span Source

Reflect a span through an arbitrary point.

normalizeSpan :: Span -> Span Source

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

_duration s = _duration (normalizeSpan s)
_midpoint s = _midpoint (normalizeSpan s)

Delay and stretch component

delayComponent :: Span -> Time Source

Access the delay component in a span.

stretchComponent :: Span -> Duration Source

Access the stretch component in a span.

fixedOnsetSpan :: Prism' Span Duration Source

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

fixedDurationSpan :: Prism' Span Time Source

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

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

isProper :: Span -> Bool Source

Deprecated: Use isForwardSpan

Whether this is a proper span, i.e. whether _onset x < _offset x.

isBefore :: Span -> Span -> Bool Source

Whether the first given span occurs before the second span.

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.

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.