-- cf. Haskore/Guitar module Sound.MIDI.ALSA.Guitar where import qualified Sound.MIDI.ALSA.Common as Common import Sound.MIDI.Message.Channel.Voice (Pitch, toPitch, fromPitch, ) import Data.Maybe (mapMaybe, ) class Transpose pitch where getPitch :: pitch -> Int transpose :: Int -> pitch -> Maybe pitch instance Transpose Pitch where getPitch = fromPitch transpose = Common.increasePitch mapChordToString :: (Transpose pitch, Ord pitch) => [Pitch] -> [pitch] -> [pitch] mapChordToString strings chord = mapMaybe (choosePitchForString chord) strings choosePitchForString :: (Transpose pitch, Ord pitch) => [pitch] -> Pitch -> Maybe pitch choosePitchForString chord string = let roundDown x d = x - mod x d minAbove x = transpose (- roundDown (getPitch x - fromPitch string) 12) x in maximum (map minAbove chord) stringPitches :: [Pitch] stringPitches = reverse $ map toPitch [40, 45, 50, 55, 59, 64] -- reverse [(-2,E), (-2,A), (-1,D), (-1,G), (-1,B), (0,E)]