-- 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

-- | Native Instruments' Reaktor softsynth.
module User.Elaforge.Instrument.Reaktor where
import qualified Data.Set as Set

import qualified Util.Doc as Doc
import qualified Cmd.Instrument.MidiInst as MidiInst
import qualified Derive.Attrs as Attrs
import qualified Derive.Controls as Controls
import qualified Derive.Instrument.DUtil as DUtil
import qualified Derive.ScoreT as ScoreT

import qualified Instrument.InstT as InstT
import qualified Midi.CC as CC
import qualified Midi.Midi as Midi
import qualified Perform.Midi.Patch as Patch

import           Global


synth :: MidiInst.Synth
synth :: Synth
synth = Text -> Text -> [Patch] -> Synth
MidiInst.synth Text
"reaktor" Text
"Native Instruments Reaktor" [Patch]
patches

resonant_filter :: MidiInst.Code
resonant_filter :: Code
resonant_filter = Generator Note -> Code
MidiInst.null_call forall a b. (a -> b) -> a -> b
$
    CallName -> Controls -> PControl -> Controls -> Generator Note
DUtil.double_pitch CallName
"res" forall a. Monoid a => a
mempty PControl
"res"
        (forall a. Ord a => [a] -> Set a
Set.fromList [Control
"mix", Control
"q", Control
"lp-hp", Control
"2-4-pole"])

patch :: InstT.Name -> [(Midi.Control, ScoreT.Control)] -> MidiInst.Patch
patch :: Text -> [(Control, Control)] -> Patch
patch = PbRange -> Text -> [(Control, Control)] -> Patch
MidiInst.named_patch (-Int
96, Int
96)

patches :: [MidiInst.Patch]
patches :: [Patch]
patches =
    -- My own patches.
    [ Patch -> Patch
MidiInst.pressure forall a b. (a -> b) -> a -> b
$ Text -> [(Control, Control)] -> Patch
patch Text
"fm1" [(Control
4, Control
"depth")]
    , Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#= Doc
"Tunable comb filter that processes an audio signal." forall a b. (a -> b) -> a -> b
$
        Text -> [(Control, Control)] -> Patch
patch Text
"comb" [(Control
1, Control
"mix"), (Control
4, Control
"fbk")]
    , Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#= Doc
"Tunable filter that processes an audio signal." forall a b. (a -> b) -> a -> b
$
        Text -> [(Control, Control)] -> Patch
patch Text
"filter"
            [ (Control
1, Control
"mix")
            , (Control
CC.cc14, Control
"q")
            , (Control
CC.cc15, Control
"lp-hp")
            , (Control
CC.cc16, Control
"2-4-pole")
            ]

    -- Factory patches.
    , Text -> [(Control, Control)] -> Patch
patch Text
"lazerbass"
        -- In 'parameter', replace bend input of 'Basic Pitch prepare' with 96,
        -- replace 'M.tr' input of 'Global P/G' with 0.
        -- Rebind ccs for c1 and c2.
        [ (Control
CC.cc14, Control
Controls.mc1), (Control
CC.cc15, Control
Controls.mc2)
        ]
    , Text -> [(Control, Control)] -> Patch
patch Text
"steam"
        -- Steampipe2, set pitch bend range to 96.
        []

    -- Commercial patches.

    , Text -> [(Control, Control)] -> Patch
patch Text
"spark"
        -- Modifications:
        -- Bind cc14 to red "filter cutoff" knob, smoothing from 50 to 10.
        -- Bind cc15 to red "filter reso" knob.
        -- Bind cc7 to "output" knob.
        -- Hardcode pitchbend range to 96 by replacing control with a constant.
        [ (Control
4, Control
Controls.mc1), (Control
11, Control
Controls.mc2), (Control
1, Control
Controls.mc3)
        , (Control
CC.cc14, Control
Controls.lpf)
        , (Control
CC.cc15, Control
Controls.q)
        ]
    , Text -> [(Control, Control)] -> Patch
patch Text
"prism"
        [ (Control
1, Control
Controls.mc1)
        , (Control
11, Control
Controls.mc2)
        ]

    -- Downloaded patches.

    , Text -> [(Control, Control)] -> Patch
patch Text
"shark"
        -- Downloaded from NI, Shark.ens.
        -- Modifications: pitchbend to 96, signal smoothers from 100ms to 10ms.
        [ (Control
4, Control
Controls.lpf), (Control
3, Control
Controls.q) -- 1st filter
        , (Control
10, Control
"color")
        ]

    , Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#= Doc
"Herald brass physical model." forall a b. (a -> b) -> a -> b
$
        -- Downloaded from NI, Herald_Brass_V2.ens.
        -- Modifications: disconnect the PM port and replace with pitch bend of
        -- 96.  Assign controls to knobs.
        -- Flutter and vib are just macros for air and emb controls, but seem
        -- useful.
        Patch -> Patch
MidiInst.pressure forall a b. (a -> b) -> a -> b
$ Text -> [(Control, Control)] -> Patch
patch Text
"herald"
            [ (Control
CC.mod, Control
Controls.vib)
            , (Control
CC.vib_speed, Control
Controls.vib_speed)
            , (Control
CC.cc14, Control
"atk") -- tongue attack
            , (Control
CC.cc15, Control
"buzz") -- tongue buzz
            , (Control
CC.cc16, Control
"buzz-len") -- tongue buzz length
            , (Control
CC.cc17, Control
"emb") -- lips embouchure
            , (Control
CC.cc18, Control
"stiff") -- lips stiffness
            -- , (CC.cc19, "noise") -- lips noise, not implemented
            , (Control
CC.cc20, Control
"finger") -- bore finger time

            , (Control
CC.cc21, Control
"flut") -- flutter tongue
            , (Control
CC.cc22, Control
"flut-speed") -- flutter tongue speed
            ]

    , Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#= Doc
"Serenade bowed string physical model." forall a b. (a -> b) -> a -> b
$
        -- Downloaded from NI, Serenade.ens.
        -- Modifications: Remove gesture and replace with a direct mapping to
        -- cc2.  Add pitch bend to pitch.  Assign controls to knobs.
        --
        -- It's important to put the pitch bend in "Bowed String", after the
        -- tuner.
        --
        -- I map breath to only one bowing direction, since deciding on which
        -- direction the bow is going all the time seems like a pain, and
        -- probably has minimal affect on the sound.  If dropping to
        -- 0 momentarily sounds like a direction change then that's good
        -- enough.
        Patch :-> Patch
MidiInst.patch forall a b c. Lens a b -> Lens b c -> Lens a c
# Patch :-> AttributeMap
Patch.attribute_map forall f a. Lens f a -> a -> f -> f
#=
            [(Control, [(Attributes, Control)])] -> AttributeMap
Patch.cc_keyswitches [(Control
CC.cc20, [(Attributes
Attrs.pizz, Control
127), (forall a. Monoid a => a
mempty, Control
0)])] forall a b. (a -> b) -> a -> b
$
        Patch -> Patch
MidiInst.pressure forall a b. (a -> b) -> a -> b
$ PbRange -> Text -> [(Control, Control)] -> Patch
MidiInst.named_patch (-Int
24, Int
24) Text
"serenade"
            [ (Control
CC.mod, Control
Controls.vib)
            , (Control
CC.vib_speed, Control
Controls.vib_speed)
            , (Control
CC.cc14, Control
"bow-speed")
            , (Control
CC.cc15, Control
"bow-force")
            , (Control
CC.cc16, Control
"bow-pos")
            , (Control
CC.cc17, Control
"string-jitter")
            , (Control
CC.cc18, Control
"string-buzz")
            , (Control
CC.cc21, Control
"pizz-tone")
            , (Control
CC.cc22, Control
"pizz-time")
            , (Control
CC.cc23, Control
"pizz-level")
            ]
    ] forall a. [a] -> [a] -> [a]
++ [Patch]
silverwood_patches

{- | Downloaded from NI, SilverwoodV3.2.ens.
    Modifications: add AR envelope to kbd gate multiplied with breath, so key
    off also causes the note to stop.  Vibrato all snap isolated, and all the
    "Mod" controls turned off.  Rate, Level1, and Level2 directly mapped to
    controls, defaults all 0.  Growl all snap isolated, destination pressure,
    level 0 and mapped.

    Replace Pitch Wheel in MIDI Mod Sources with constant 0, and replace
    transpose with PitchBend in Pitch.

    Each model has different controls, and the controls that aren't mapped to
    air pressure or note number are simplified to be directly controllable from
    MIDI.  That is, I delete everything except the \"Amount\" knob, and tune its
    range to be what sounds useful for that model.

    - sax (oboe, english horn, bassoon, harmonica, accordion, uillean pipes,
    scots pipes): exc. pt (0--?), effic. (-1--?)

    - clarinet: register (0--0.5)

    - flute (piccolo, irish whistle, shakuhachi): embouch (-45--45)

    - recorder (pan pipes): none

    - brass (trumpet, cornet, flugelhorn, french horn, trombone, euphonium,
    tuba): embouch (-45--45)

    Nothing for organ model yet, I don't really care much about organs.
-}
silverwood_patches :: [MidiInst.Patch]
silverwood_patches :: [Patch]
silverwood_patches =
    [ Text -> [(Control, Control)] -> Patch
mk Text
"clarinet" [(Control
CC.cc16, Control
"register")]
    , Text -> [(Control, Control)] -> Patch
mk Text
"flute" [(Control
CC.cc17, Control
"embouch")]
    , Text -> [(Control, Control)] -> Patch
mk Text
"brass" [(Control
CC.cc17, Control
"embouch")]
    , Text -> [(Control, Control)] -> Patch
mk Text
"sax" [(Control
CC.cc18, Control
"exc"), (Control
CC.cc19, Control
"effic")]
    , Text -> [(Control, Control)] -> Patch
mk Text
"recorder" []
    ]
    where
    mk :: Text -> [(Control, Control)] -> Patch
mk Text
name [(Control, Control)]
controls =
        Lens Patch Doc
MidiInst.doc forall f a. Lens f a -> a -> f -> f
#=
            (Doc
"Silverwood woodwind physical model: " forall a. Semigroup a => a -> a -> a
<> Text -> Doc
Doc.Doc Text
name) forall a b. (a -> b) -> a -> b
$
        Patch -> Patch
MidiInst.pressure forall a b. (a -> b) -> a -> b
$ Text -> [(Control, Control)] -> Patch
patch (Text
"sw-" forall a. Semigroup a => a -> a -> a
<> Text
name) forall a b. (a -> b) -> a -> b
$
            [ (Control
CC.mod, Control
Controls.vib)
            , (Control
CC.vib_speed, Control
Controls.vib_speed)
            , (Control
CC.cc14, Control
"trem") -- brightness "vibrato", destination 1
            , (Control
CC.cc15, Control
"growl")
            ] forall a. [a] -> [a] -> [a]
++ [(Control, Control)]
controls