Copyright | (c) 2012--2016 Chordify BV |
---|---|
License | LGPL-3 |
Maintainer | haskelldevelopers@chordify.net |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Summary: A set of types and classes for representing musical time, mainly (but not necessarily) in the context of recognising chords from an arbitrary audio source.
- type Timed a = Timed' Float a
- type DTimed a = Timed' Double a
- data Timed' t a = Timed {
- getData :: a
- getTimeStamps :: [BeatTime t]
- data Beat
- data BeatTime a
- data MeterKind
- newtype BPM = BPM {}
- timed :: Fractional t => a -> t -> t -> Timed' t a
- timedBT :: Fractional t => a -> BeatTime t -> BeatTime t -> Timed' t a
- onBeatTime :: Fractional t => Timed' t a -> BeatTime t
- offBeatTime :: Fractional t => Timed' t a -> BeatTime t
- onBeat :: Timed a -> Beat
- offBeat :: Timed a -> Beat
- onset :: Fractional t => Timed' t a -> t
- offset :: Fractional t => Timed' t a -> t
- duration :: Fractional t => Timed' t a -> t
- setData :: Timed a -> b -> Timed b
- getEndTime :: Fractional t => [Timed' t a] -> t
- mergeTimed :: Eq a => [Timed a] -> [Timed a]
- mergeTimedWith :: forall a. Eq a => (a -> a -> Bool) -> [Timed a] -> [Timed a]
- expandTimed :: [Timed a] -> [Timed a]
- concatTimed :: a -> Timed a -> Timed a -> Timed a
- splitTimed :: (Show a, Ord t, Show t, Fractional t) => Timed' t a -> t -> (Timed' t a, Timed' t a)
- setMeterKind :: MeterKind -> [Timed a] -> [Timed a]
- updateBeats :: MeterKind -> Beat -> [Timed a] -> [Timed a]
- updateBeat :: MeterKind -> Beat -> Timed a -> Timed a
- splitPickup :: [Timed a] -> ([Timed a], [Timed a])
- nextBeat :: MeterKind -> Beat -> Beat
- prevBeat :: MeterKind -> Beat -> Beat
- lastBeat :: MeterKind -> Beat
- updBeat :: Fractional t => (Beat -> Beat) -> BeatTime t -> BeatTime t
- updTime :: Fractional t => (t -> t) -> BeatTime t -> BeatTime t
- updateTimeStamp :: Fractional t => ([BeatTime t] -> [BeatTime t]) -> Timed' t a -> Timed' t a
- dropTimed :: [Timed a] -> [a]
- timeStamp :: Fractional t => BeatTime t -> t
- timeComp :: (Ord t, Fractional t) => t -> t -> Ordering
- roundingError :: Fractional t => t
- beat :: BeatTime t -> Beat
- pprint :: Show a => Timed a -> String
- prettyPrint :: Show a => [Timed a] -> String
- estimateTempo :: [Timed a] -> BPM
Representing musical time
A datatype that wraps around an (musical) datatype, adding information
about the musical time to this datatype. Musical time is stored as
a list of BeatTime
time stamps that can optionally be augmented
with information about the Beat
position of the particular time stamp
inside the bar.
Timed | |
|
For now, we fix the number of available beats to four, because this is also hard-coded into the bar and beat-tracker.
Represents a musical time stamp, which is a NumData
possibly augmented
with a Beat
denoting the position of the time stamp within a bar.
Number of beats per minute
Functions
Data access
timedBT :: Fractional t => a -> BeatTime t -> BeatTime t -> Timed' t a Source #
alternative Timed
constructor
onBeatTime :: Fractional t => Timed' t a -> BeatTime t Source #
Returns the start BeatTime
offBeatTime :: Fractional t => Timed' t a -> BeatTime t Source #
Returns the offset time stamp
onset :: Fractional t => Timed' t a -> t Source #
Returns the onset time stamp
offset :: Fractional t => Timed' t a -> t Source #
Returns the offset time stamp
getEndTime :: Fractional t => [Timed' t a] -> t Source #
Given a list of Timed
values, returns the end time of the latest element
in the list.
Type conversion and other utilities
mergeTimed :: Eq a => [Timed a] -> [Timed a] Source #
merges consecutive Timed
values that store the same element (using
('(==)'). For example:
>>>
mergeTimed [timed "c" 0 1, timed "c" 1 2, timed "d" 3 4, timed "d" 4 5, timed "e" 5 6]
>>>
[Timed {getData = "c", getTimeStamps = [(0.0),(1.0),(2.0)]}
>>>
,Timed {getData = "d", getTimeStamps = [(3.0),(4.0),(5.0)]}
>>>
,Timed {getData = "e", getTimeStamps = [(5.0),(6.0)]}]
mergeTimedWith :: forall a. Eq a => (a -> a -> Bool) -> [Timed a] -> [Timed a] Source #
Does exactly what mergeTimed
does, but allows for a custom equality
function
expandTimed :: [Timed a] -> [Timed a] Source #
the inverse of mergeTimed
, expanding the list Timed
elements to all
timestamps stored in the getTimeStamps
list. N.B.
>>>
expandTimed (mergeTimed x) = x :: [Timed a]
also,
>>>
(expandTimed cs) = cs
and,
>>>
mergeTimed (mergeTimed (mergeTimed cs)) = (mergeTimed cs)
hold. This has been tested on the first tranche of 649 Billboard songs.
splitTimed :: (Show a, Ord t, Show t, Fractional t) => Timed' t a -> t -> (Timed' t a, Timed' t a) Source #
updateBeats :: MeterKind -> Beat -> [Timed a] -> [Timed a] Source #
applies updateBeat to a list. updateBeats
requires a MeterKind
and a starting Beat
.
>>>
updateBeats Triple Three [ timedBT "a" (BeatTime 0 Three) (BeatTime 1 Four)
>>>
, timedBT "a" (BeatTime 1 Four) (BeatTime 2 One)
>>>
, Timed "a" [ BeatTime 2 One, BeatTime 3 Two
>>>
, BeatTime 4 Three, BeatTime 5 Four]]
>>>
[Timed {getData = "a", getTimeStamps = [(0.0, 3),(1.0, 1)]}
>>>
,Timed {getData = "a", getTimeStamps = [(1.0, 1),(2.0, 2)]}
>>>
,Timed {getData = "a", getTimeStamps = [(2.0, 2),(3.0, 3),(4.0, 1),(5.0, 2)]}]
splitPickup :: [Timed a] -> ([Timed a], [Timed a]) Source #
N.B. calls expandTimed
before splitting
nextBeat :: MeterKind -> Beat -> Beat Source #
returns the next beat, e.g. nextBeat Two = Three
.
Following the (current) definition of Beat
, we still assume 4/4, in the
future this function should also have the meter as an argument.
N.B. nextBeat Four = One
updTime :: Fractional t => (t -> t) -> BeatTime t -> BeatTime t Source #
updates a timestamp in a BeatTime
updateTimeStamp :: Fractional t => ([BeatTime t] -> [BeatTime t]) -> Timed' t a -> Timed' t a Source #
updates the timestamps in a Timed
datatype
timeStamp :: Fractional t => BeatTime t -> t Source #
Returns the NumData
timestamp, given a BeatTime
timeComp :: (Ord t, Fractional t) => t -> t -> Ordering Source #
compares to NumData
timestamps taking a rounding error roundingError
into account.
roundingError :: Fractional t => t Source #
When reducing and expanding Timed
types there might be rounding
errors in the floating point time stamps. The roundingError
parameter
sets the acceptable rounding error that is used in the comparison of
time stamps (e.g. see timeComp
)
estimateTempo :: [Timed a] -> BPM Source #
Estimate the tempo of the song by taking the median of the timestamps. The result is returned as the number of semiquavers per minute.