| Copyright | (c) Hans Hoglund 2012-2014 |
|---|---|
| License | BSD-style |
| Maintainer | hans@hanshoglund.se |
| Stability | experimental |
| Portability | non-portable (TF,GNTD) |
| Safe Haskell | None |
| Language | Haskell2010 |
Music.Time.Types
Contents
Description
- data Time
- toTime :: Real a => a -> Time
- fromTime :: Fractional a => Time -> a
- data Duration
- toDuration :: Real a => a -> Duration
- fromDuration :: Fractional a => Duration -> a
- offsetPoints :: AffineSpace a => a -> [Diff a] -> [a]
- toAbsoluteTime :: [Duration] -> [Time]
- toRelativeTime :: [Time] -> [Duration]
- toRelativeTimeN :: [Time] -> [Duration]
- toRelativeTimeN' :: Time -> [Time] -> [Duration]
- data Span
- (<->) :: Time -> Time -> Span
- (>->) :: Time -> Duration -> Span
- (<-<) :: Duration -> Time -> Span
- range :: Iso' Span (Time, Time)
- delta :: Iso' Span (Time, Duration)
- codelta :: Iso' Span (Duration, Time)
- isForwardSpan :: Span -> Bool
- isBackwardSpan :: Span -> Bool
- isEmptySpan :: Span -> Bool
- reverseSpan :: Span -> Span
- reflectSpan :: Time -> Span -> Span
- normalizeSpan :: Span -> Span
- delayComponent :: Span -> Time
- stretchComponent :: Span -> Duration
- fixedOnsetSpan :: Prism' Span Duration
- fixedDurationSpan :: Prism' Span Time
- inside :: Time -> Span -> Bool
- isProper :: Span -> Bool
- isBefore :: Span -> Span -> Bool
- encloses :: Span -> Span -> Bool
- properlyEncloses :: Span -> Span -> Bool
- overlaps :: Span -> Span -> Bool
- afterOnset :: Time -> Span -> Bool
- strictlyAfterOnset :: Time -> Span -> Bool
- beforeOnset :: Time -> Span -> Bool
- strictlyBeforeOnset :: Time -> Span -> Bool
- afterOffset :: Time -> Span -> Bool
- strictlyAfterOffset :: Time -> Span -> Bool
- beforeOffset :: Time -> Span -> Bool
- strictlyBeforeOffset :: Time -> Span -> Bool
- startsWhenStarts :: Span -> Span -> Bool
- startsWhenStops :: Span -> Span -> Bool
- stopsWhenStops :: Span -> Span -> Bool
- stopsWhenStarts :: Span -> Span -> Bool
- startsBefore :: Span -> Span -> Bool
- startsLater :: Span -> Span -> Bool
- stopsAtTheSameTime :: Span -> Span -> Bool
- stopsBefore :: Span -> Span -> Bool
- stopsLater :: Span -> Span -> Bool
- showRange :: Span -> String
- showDelta :: Span -> String
- showCodelta :: Span -> String
Basic types
Time points
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.
Instances
fromTime :: Fractional a => Time -> a Source
Convert a value to a duration.
Duration
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.
Instances
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 ::AffineSpacea =>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
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 (viewrange-> (t1, t2)) = ... foo (viewdelta-> (t1, d)) = ... foo (viewcodelta-> (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)^.fromrangea>->b = (a, b)^.fromdeltaa<-<b = (a, b)^.fromcodelta
Instances
| Eq Span | |
| Ord Span | |
| Show Span | |
| ToJSON Span | |
| Monoid Span |
|
| Semigroup Span |
|
| AdditiveGroup Span |
|
| Transformable Span | |
| HasDuration Span | |
| HasPosition Span | |
| Splittable Span | |
| Reversible Span | |
| Typeable * Span |
Creating spans
Accessing spans
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 <-> 2False
>>>1.5 `inside` 1 <-> 2True
>>>1 `inside` 1 <-> 2True
Partial orders
isProper :: Span -> Bool Source
Deprecated: Use isForwardSpan
Whether this is a proper span, i.e. whether ._onset x < _offset x
encloses :: Span -> Span -> Bool infixl 5 Source
Whether the first given span encloses the second span.
>>>0 <-> 3 `encloses` 1 <-> 2True
>>>0 <-> 2 `encloses` 1 <-> 2True
>>>1 <-> 3 `encloses` 1 <-> 2True
>>>1 <-> 2 `encloses` 1 <-> 2True
properlyEncloses :: Span -> Span -> Bool infixl 5 Source
Whether the first given span encloses the second span.
>>>0 <-> 3 `properlyEncloses` 1 <-> 2True
>>>0 <-> 2 `properlyEncloses` 1 <-> 2True
>>>1 <-> 3 `properlyEncloses` 1 <-> 2True
>>>1 <-> 2 `properlyEncloses` 1 <-> 2False
afterOnset :: Time -> Span -> Bool Source
strictlyAfterOnset :: Time -> Span -> Bool Source
beforeOnset :: Time -> Span -> Bool Source
strictlyBeforeOnset :: Time -> Span -> Bool Source
afterOffset :: Time -> Span -> Bool Source
strictlyAfterOffset :: Time -> Span -> Bool Source
beforeOffset :: Time -> Span -> Bool Source
strictlyBeforeOffset :: Time -> Span -> Bool Source
startsWhenStarts :: Span -> Span -> Bool Source
startsWhenStops :: Span -> Span -> Bool Source
stopsWhenStops :: Span -> Span -> Bool Source
stopsWhenStarts :: Span -> Span -> Bool Source
startsBefore :: Span -> Span -> Bool Source
startsLater :: Span -> Span -> Bool Source
stopsAtTheSameTime :: Span -> Span -> Bool Source
stopsBefore :: Span -> Span -> Bool Source
stopsLater :: Span -> Span -> Bool Source
Read/Show
showCodelta :: Span -> String Source
Show a span in codelta notation, i.e. t <-< d.