fadno-1.1.0: Minimal library for music generation and notation

Safe HaskellNone
LanguageHaskell2010

Fadno.Meter

Synopsis

Documentation

rebars :: (HasRatioNotes b n p, HasRatioNotes c m p, Monoid p, Eq p, Monoid (c m), Monoid (b n), HasTimeSignature (c m), Snoc (c m) (c m) m m, HasTie m, Show (c m)) => TimeSignature -> [b n] -> [c m] Source #

use rebar with multiple input "bars".

rebar :: (HasRatioNotes b n p, HasRatioNotes c m p, Monoid p, Eq p, Monoid (c m), HasTimeSignature (c m), Snoc (c m) (c m) m m, HasTie m, Show (c m)) => TimeSignature -> b n -> [c m] Source #

Given a time signature and a "bar" (Traversable "b" of HasNotes "n"), make new "bars" (Traversable "c" of HasNotes "m"), partitioning notes, applying ties as needed, and decorating with the time signature.

rebar' :: (HasRatioNotes b n p, Monoid p, Eq p, Show p) => TimeSignature -> b n -> [Bar (Note' p Rational)] Source #

rebar using Bar and 'Note\'' for output.

rebars' :: (HasRatioNotes b n p, Monoid (b n), Monoid p, Eq p, Show p) => TimeSignature -> [b n] -> [Bar (Note' p Rational)] Source #

rebars using Bar and 'Note\'' for output.

tieMay :: (Eq a, Monoid a, HasNote s a d, HasTie s) => Tie -> s -> s Source #

Set tie if not a rest

validDenoms :: [Integer] Source #

Representable duration denominators.

For standard base-2 durs, 2 and 4 are spurious as they reduce to 1, thus 1 plus the "dot values" 3,7.

For non-standard (quintuples etc), we admit 2 and 4 as well, for e.g. 2%5, a "half-note" under a quarter-quintuple. Anything greater exceeding the understanding limit: 8%17 can certainly be represented as a half-note, but it makes little sense to the reader.

maxDur :: Rational Source #

Max representable duration.

validDur :: Rational -> Bool Source #

Test for representational duration per validDenoms and maxDur.

splitDur :: Rational -> [Rational] Source #

Tie rules that work across any denominators, such that 5%8 -> [1%2,1%8], 9%16 -> [1%2,1%16], 11%16 -> [1%2,3%16], 13%16 -> [3%2,1%16], 9%4 -> [2,1%4].

findSplit :: Rational -> Rational Source #

Find split by 1) finding largest power-of-2 fraction under value or 2) finding longest power-of-two denominator split, up to 8.

tieRules :: (HasRatioNotes b n p, HasTie n, Monoid p, Eq p, Show n, HasRatioNotes c m p, HasTie m, Monoid (c m), Snoc (c m) (c m) m m) => b n -> c m Source #

Apply rules in splitDur and tie affected notes.

tieRules' :: (HasRatioNotes b n p, HasTie n, Monoid p, Eq p, Show n) => b n -> Bar (Note' p Rational) Source #

Monomorphic-result 'tieRules

data TsConfig Source #

Weights and pulse values for pre-configured TSs.

Constructors

TsConfig 

selectTimeSigs :: HasRatioNotes t n p => [t n] -> [(TimeSignature, Rational)] Source #

Combine scores from phrases.

preferDivisableHeads :: [[TsConfig]] -> [[TsConfig]] Source #

nutty heuristic that overweights a TS for a uniform duration divisor

commonDivHeur :: Rational -> Rational -> Rational Source #

main heuristic is finding the common divisible duration, with requirement that it must be greater than 1/4 the difference between the durations. Hopefully avoids crappy tiny TSs like 2/8.

tsConfigFromDur :: Rational -> Rational -> Maybe TsConfig Source #

Attempt to construct a TS config from duration

tsConfigs :: [TsConfig] Source #

Pre-configured timesigs.

minMedianDur :: Quanta -> Rational Source #

Given a median note duration, minima for acceptable quanta.

selectTsConfigs :: HasRatioNotes t n p => t n -> [TsConfig] Source #

Given a phrase, select configs

evalTsConfig :: HasRatioNotes t n p => t n -> TsConfig -> Maybe TsConfig Source #

Filter and score time signatures per heuristics.

frem :: RealFrac a => a -> a -> a Source #

isDivBy :: RealFrac a => a -> a -> Bool Source #

pulseCoverage :: HasRatioNotes t n p => Rational -> t n -> Rational Source #

Compute percentage of notes falling on pulse values.