-- Copyright 2013 Evan Laforge
-- This program is distributed under the terms of the GNU General Public
-- License 3.0, see COPYING or http://www.gnu.org/licenses/gpl-3.0.txt

-- | Image-Line's Drumaxx softsynth.
module User.Elaforge.Instrument.Drumaxx where
import qualified Data.Set as Set

import Midi.Key
import qualified Midi.Midi as Midi
import qualified Cmd.Instrument.CUtil as CUtil
import qualified Cmd.Instrument.Drums as Drums
import qualified Cmd.Instrument.MidiInst as MidiInst

import Derive.Attrs
import qualified Derive.Instrument.DUtil as DUtil
import Global


synth :: MidiInst.Synth
synth :: Synth
synth = Name -> Name -> [Patch] -> Synth
MidiInst.synth Name
"drumaxx" Name
"Imagine-Line Drumaxx" [Patch]
patches

patches :: [MidiInst.Patch]
patches :: [Patch]
patches =
    [ Lens Patch Code
MidiInst.code forall f a. Lens f a -> a -> f -> f
#= Thru -> [Stroke] -> Code
CUtil.drum_code_ Thru
CUtil.MidiThru (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Stroke, Key)]
stroke_keys) forall a b. (a -> b) -> a -> b
$
        [(Stroke, Key)] -> Patch -> Patch
CUtil.drum_patch [(Stroke, Key)]
stroke_keys forall a b. (a -> b) -> a -> b
$ PbRange -> [(Control, Control)] -> Patch
MidiInst.default_patch PbRange
pb_range []
    , Lens Patch Code
MidiInst.code forall f a. Lens f a -> a -> f -> f
#= Code
composite_code forall a b. (a -> b) -> a -> b
$
        Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#= Doc
composite_doc forall a b. (a -> b) -> a -> b
$
        PbRange -> Name -> [(Control, Control)] -> Patch
MidiInst.named_patch PbRange
pb_range Name
"comb" []
    ]
    where
    composite_code :: Code
composite_code = [(Symbol, Generator Note)] -> Code
MidiInst.note_generators
        [(Symbol
call, Symbol -> Generator Note
composite Symbol
call) | Symbol
call <- forall a b. (a -> b) -> [a] -> [b]
map (Stroke -> Symbol
Drums._name forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Stroke, Key)]
stroke_keys]
    composite :: Symbol -> Generator Note
composite Symbol
call = CallName
-> Symbol -> Controls -> Symbol -> Controls -> Generator Note
DUtil.redirect_pitch CallName
"comb"
        Symbol
"" (forall a. Ord a => [a] -> Set a
Set.fromList [Control
"mix", Control
"fbk"]) Symbol
call forall a. Monoid a => a
mempty
    composite_doc :: Doc
composite_doc = Doc
"This drum takes a pitch signal, which is then sent\
        \ to the `composite-pitched` instrument, which is a tuned comb filter.\
        \ The audio routing has to be set up in the VST host."
    pb_range :: PbRange
pb_range = (-Int
24, Int
24)

-- | The octave numbers on the drumaxx are one greater than the standard
-- usage.  This is for \"Acoustic 2 FG\".  I'll have to come up with
-- a standard mapping later.
stroke_keys :: [(Drums.Stroke, Midi.Key)]
stroke_keys :: [(Stroke, Key)]
stroke_keys =
    [ (Stroke
Drums.c_bd, Key
c2)
    , (Stroke
Drums.c_bd2, Key
b1)
    , (Stroke
Drums.c_sn, Key
d2)
    , (Stroke
Drums.c_sn2, Key
e2)
    , (Char -> Symbol -> Attributes -> Stroke
Drums.stroke Char
'c' Symbol
"sn3" (Attributes
snare forall a. Semigroup a => a -> a -> a
<> Attributes
v3), Key
ds2)
    , (Stroke
Drums.c_rim, Key
cs2)
    , (Stroke
Drums.c_ltom, Key
g2)
    , (Stroke
Drums.c_mtom, Key
b2)
    , (Stroke
Drums.c_htom, Key
c3)
    , (Stroke
Drums.c_hh, Key
fs2)
    , (Stroke
Drums.c_ohh, Key
as2)
    , (Stroke
Drums.c_ride, Key
ds3)
    , (Stroke
Drums.c_crash, Key
cs3)
    ]