{-# LANGUAGE NoMonomorphismRestriction #-} -- | Module defines two musical structures 'Note' and 'Drum' and provides -- constructor-shortcuts for them. Value of type 'Note' contains -- pitch and volume. Value of type 'Drum' is just 'Volume' module Temporal.Music.Notation.Note( -- * Types Note(..), absNote, Drum(..), absDrum, -- * Shortcuts -- | Shortcuts for rests, notes and drums construction. -- Naming conventions : name has two parts, first describes duration of -- resulting score and second describes that result is rest, note or -- drum note. -- -- For name @xy@ -- -- First part @x@ can be [b | w | h | q | e | s | t | d[x] ] -- -- @b@ means brewis (duration is 2) -- -- @w@ means whole (duration is 1) -- -- @h@ means half (duration is 1/2) -- -- @q@ means quater (duration is 1/4) -- -- @e@ means eighth (duration is 1/8) -- -- @s@ means sixteenth (duration is 1/16) -- -- @t@ means thirty second (duration is 1/32) -- -- @d[x]@ means dotted [x] (stretch 1.5 $ x) -- -- Second part @y@ can be [nr | n | d] -- -- @nr@ means rest -- -- @n@ means result contains 'Note' -- -- @d@ means result contains 'Drum' -- ** Rests bnr, wnr, hnr, qnr, enr, snr, tnr, dbnr, dwnr, dhnr, dqnr, denr, dsnr, dtnr, -- ** Notes -- -- | It is assumed here that for 'Note' most important information is -- tone and shortcuts construct 'Note' values from 'Tone' 's, -- other values are set to default values. It means that scale is -- equaly tempered, bend is set to zero, volume level is set to -- mediumLevel, -- accent is set to zero and volume diapason is set to interval (1e-5, 1). -- bn, wn, hn, qn, en, sn, tn, dbn, dwn, dhn, dqn, den, dsn, dtn, -- ** Drums -- -- | It is assumed here that for 'Drum' most important information is -- accent and shortcuts construct 'Drum' from 'Accent' 's, other -- parameters are set to default values. It means that volume level -- is mediumLevel and volume diapason is (1e-5, 1) bd, wd, hd, qd, ed, sd, td, dbd, dwd, dhd, dqd, ded, dsd, dtd ) where import TypeLevel.NaturalNumber(NaturalNumber) import Temporal.Music.Notation.Pitch import Temporal.Music.Notation.Volume import Temporal.Music.Notation.Score (Dur, Score, note, rest, dot) import Temporal.Music.Notation.Local.Scales(eqts) -- Note -- | Value of type 'Note' contains pitch, volume and some specific -- timbre information. data (NaturalNumber nVol, NaturalNumber nPch) => Note nVol nPch = Note { noteVolume :: Volume nVol , notePitch :: Pitch nPch } deriving (Show, Eq) -- volume instances instance (NaturalNumber nVol, NaturalNumber nPch) => VolFunctor (Note nVol nPch) where mapVol f (Note v p) = Note (f v) p instance (NaturalNumber nVol, NaturalNumber nPch) => LevelFunctor (Note nVol nPch) where mapLevel f (Note v p) = Note (mapLevel f v) p -- pitch instances instance (NaturalNumber nVol, NaturalNumber nPch) => PchFunctor (Note nVol nPch) where mapPch f (Note v p) = Note v (f p) instance (NaturalNumber nVol, NaturalNumber nPch) => ScaleFunctor (Note nVol nPch) where mapScale f (Note v p) = Note v (mapScale f p) instance (NaturalNumber nVol, NaturalNumber nPch) => ToneFunctor (Note nVol nPch) where mapTone f (Note v p) = Note v (mapTone f p) -- | calculates 'absVolume' and 'absPitch' on notes absNote :: (NaturalNumber nVol, NaturalNumber nPch) => Note nVol nPch -> (Amplitude, Frequency) absNote (Note v p) = (absVolume v, absPitch p) -- Drum -- | Value of type 'Drum' is just 'Volume'. type Drum n = Volume n -- | synonym for 'absVolume' absDrum :: (NaturalNumber nVol) => Drum nVol -> Amplitude absDrum = absVolume -- shortcuts defaultVolume :: NaturalNumber n => Volume n defaultVolume = Volume (1e-5, 1) mediumLevel -- notes n :: (NaturalNumber nVol, NaturalNumber nPch) => Dur -> Tone nPch -> Score (Note nVol nPch) n dt t = note dt $ Note defaultVolume (Pitch (eqts 0 c1) t) bn, wn, hn, en, sn, tn, dbn, dwn, dhn, den, dsn, dtn :: (NaturalNumber nVol, NaturalNumber nPch) => Tone nPch -> Score (Note nVol nPch) bn = n 2 wn = n 1 hn = n 0.5 qn = n 0.25 en = n 0.125 sn = n 0.0625 tn = n 0.03125 dbn = dot . bn dwn = dot . wn dhn = dot . hn dqn = dot . qn den = dot . en dsn = dot . sn dtn = dot . tn -- drums d :: (NaturalNumber nVol) => Dur -> Accent -> Score (Drum nVol) d dt a = note dt $ setAccent a defaultVolume -- | brevis note rest bd, wd, hd, ed, sd, td, dbd, dwd, dhd, ded, dsd, dtd :: (NaturalNumber nVol) => Accent -> Score (Drum nVol) bd = d 2 wd = d 1 hd = d 0.5 qd = d 0.25 ed = d 0.125 sd = d 0.0625 td = d 0.03125 dbd = dot . bd dwd = dot . wd dhd = dot . hd dqd = dot . qd ded = dot . ed dsd = dot . sd dtd = dot . td -- rests -- bnr, wnr, hnr, qnr, enr, snr, tnr, dbnr, dwnr, dhnr, dqnr, denr, dsnr, dtnr :: Score a bnr = rest 2 wnr = rest 1 hnr = rest 0.5 qnr = rest 0.25 enr = rest 0.125 snr = rest 0.0625 tnr = rest 0.03125 dbnr = dot $ bnr dwnr = dot $ wnr dhnr = dot $ hnr dqnr = dot $ qnr denr = dot $ enr dsnr = dot $ snr dtnr = dot $ tnr