{-# LANGUAGE NoImplicitPrelude #-} {- | Functions for converting MIDI controller and key values to something meaningful for signal processing. -} module Synthesizer.Dimensional.MIDIValue where import qualified Sound.MIDI.Message.Channel.Voice as VoiceMsg import qualified Algebra.DimensionTerm as Dim import qualified Number.DimensionTerm as DN import qualified Algebra.Transcendental as Trans import qualified Algebra.Field as Field import qualified Algebra.Additive as Additive import NumericPrelude.Numeric -- import NumericPrelude.Base {-# INLINE controllerLinear #-} controllerLinear :: (Field.C y, Dim.C v) => DN.T v y -> (DN.T v y, DN.T v y) -> Int -> y controllerLinear amp (lower,upper) n = let k = fromIntegral n / 127 in DN.divToScalar (DN.scale (1-k) lower + DN.scale k upper) amp {-# INLINE controllerExponential #-} controllerExponential :: (Trans.C y, Dim.C v) => DN.T v y -> (DN.T v y, DN.T v y) -> Int -> y controllerExponential amp (lower,upper) n = let k = fromIntegral n / 127 in DN.divToScalar lower amp ** (1-k) * DN.divToScalar upper amp ** k {-# INLINE pitchBend #-} pitchBend :: (Trans.C y, Dim.C v) => DN.T v y -> y -> DN.T v y -> Int -> y pitchBend amp range center n = DN.divToScalar center amp * range ** (fromIntegral n / 8192) {- | Convert pitch to frequency according to the default tuning in MIDI 1.0 Detailed Specification. -} {-# INLINE frequencyFromPitch #-} frequencyFromPitch :: (Trans.C y) => VoiceMsg.Pitch -> DN.Frequency y frequencyFromPitch pitch = DN.scale (2 ^? (fromIntegral (VoiceMsg.fromPitch pitch + 3 - 6*12) / 12)) (DN.frequency 440)