module Cmd.Repl.LAlloc where
import qualified Cmd.Instrument.ImInst as ImInst
import qualified Cmd.Instrument.MidiInst as MidiInst
import qualified Derive.C.Bali.Gangsa as Gangsa
import qualified Derive.Scale.BaliScales as BaliScales
import qualified Derive.Scale.Legong as Legong
import qualified Derive.ScoreT as ScoreT
import qualified Instrument.Common as Common
import qualified Instrument.InstT as InstT
import qualified Midi.Midi as Midi
import qualified Perform.Midi.Patch as Patch
import qualified Synth.Sampler.Patch.KendangBali as Sampler.Patch.KendangBali
import qualified Ui.UiConfig as UiConfig
import qualified User.Elaforge.Instrument.Kontakt.KendangBali as KendangBali
import qualified User.Elaforge.Instrument.Kontakt.ScGamelan as ScGamelan
import Global
rambat_im :: UiConfig.Allocations
rambat_im :: Allocations
rambat_im =
Verbosity
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_im Verbosity
Short Text
"ra" Tuning
BaliScales.Umbang
Text -> Qualified
sampler Text
"rambat" Text
"rambat-umbang" Text
"rambat-isep"
wayang_im :: Text -> Text -> UiConfig.Allocations
wayang_im :: Text -> Text -> Allocations
wayang_im Text
pemade Text
kantilan =
Verbosity
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_im Verbosity
Short Text
pemade Tuning
BaliScales.Umbang
Text -> Qualified
sampler Text
"wayang-pemade" Text
"wayang-pemade-umbang" Text
"wayang-pemade-isep"
forall a. Semigroup a => a -> a -> a
<> Verbosity
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_im Verbosity
Short Text
kantilan Tuning
BaliScales.Umbang
Text -> Qualified
sampler Text
"wayang-kantilan"
Text
"wayang-kantilan-umbang" Text
"wayang-kantilan-isep"
sampler :: Text -> InstT.Qualified
sampler :: Text -> Qualified
sampler = Text -> Text -> Qualified
InstT.Qualified Text
"sampler"
wayang_midi :: Text -> Text -> Text -> UiConfig.Allocations
wayang_midi :: Text -> Text -> Text -> Allocations
wayang_midi Text
dev_ Text
pemade Text
kantilan =
Verbosity
-> WriteDevice
-> Channel
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_midi Verbosity
Short WriteDevice
dev Channel
0 Text
pemade Tuning
BaliScales.Umbang
Text -> Qualified
kontakt Text
"wayang-pemade" Text
"wayang-umbang" Text
"wayang-isep"
forall a. Semigroup a => a -> a -> a
<> Verbosity
-> WriteDevice
-> Channel
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_midi Verbosity
Short WriteDevice
dev Channel
2 Text
kantilan Tuning
BaliScales.Umbang
Text -> Qualified
kontakt Text
"wayang-kantilan" Text
"wayang-umbang" Text
"wayang-isep"
where
dev :: WriteDevice
dev = Text -> WriteDevice
Midi.write_device Text
dev_
kontakt :: Text -> InstT.Qualified
kontakt :: Text -> Qualified
kontakt = Text -> Text -> Qualified
InstT.Qualified Text
"kontakt"
data Verbosity = Long | Short deriving (Verbosity -> Verbosity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> String
$cshow :: Verbosity -> String
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show)
pasang_im :: Verbosity -> Text -> BaliScales.Tuning -> (Text -> InstT.Qualified)
-> Text -> Text -> Text -> UiConfig.Allocations
pasang_im :: Verbosity
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_im Verbosity
verbosity Text
base Tuning
polos_tuning
Text -> Qualified
qualify Text
pasang_qual Text
umbang_qual Text
isep_qual =
[(Instrument, Qualified, Config -> Config, Backend)] -> Allocations
ImInst.allocations
[ (Text -> Instrument
inst Text
base, Text -> Qualified
qualify Text
pasang_qual, Config -> Config
pasang, Text -> Backend
UiConfig.Dummy Text
"")
, (Instrument
umbang, Text -> Qualified
qualify Text
umbang_qual, forall a. a -> a
id, Backend
UiConfig.Im)
, (Instrument
isep, Text -> Qualified
qualify Text
isep_qual, forall a. a -> a
id, Backend
UiConfig.Im)
]
where
umbang :: Instrument
umbang = Text -> Instrument
inst forall a b. (a -> b) -> a -> b
$ Text
base forall a. Semigroup a => a -> a -> a
<> case Verbosity
verbosity of
Verbosity
Long -> Text
"-umbang"
Verbosity
Short -> Text
"u"
isep :: Instrument
isep = Text -> Instrument
inst forall a b. (a -> b) -> a -> b
$ Text
base forall a. Semigroup a => a -> a -> a
<> case Verbosity
verbosity of
Verbosity
Long -> Text
"-isep"
Verbosity
Short -> Text
"i"
pasang :: Config -> Config
pasang = Tuning -> Instrument -> Instrument -> Config -> Config
make_pasang Tuning
polos_tuning Instrument
umbang Instrument
isep
inst :: Text -> Instrument
inst = Text -> Instrument
ScoreT.Instrument
pasang_midi :: Verbosity -> Midi.WriteDevice -> Midi.Channel -> Text
-> BaliScales.Tuning -> (Text -> InstT.Qualified) -> Text -> Text -> Text
-> UiConfig.Allocations
pasang_midi :: Verbosity
-> WriteDevice
-> Channel
-> Text
-> Tuning
-> (Text -> Qualified)
-> Text
-> Text
-> Text
-> Allocations
pasang_midi Verbosity
verbosity WriteDevice
dev Channel
chan Text
base Tuning
polos_tuning
Text -> Qualified
qualify Text
pasang_qual Text
umbang_qual Text
isep_qual =
[(Instrument, Qualified, Config -> Config, Backend)] -> Allocations
MidiInst.allocations
[ (Text -> Instrument
inst Text
base, Text -> Qualified
qualify Text
pasang_qual, Config -> Config
pasang, Text -> Backend
UiConfig.Dummy Text
"")
, (Instrument
umbang, Text -> Qualified
qualify Text
umbang_qual, forall a. a -> a
id, Channel -> Backend
midi_channel Channel
0)
, (Instrument
isep, Text -> Qualified
qualify Text
isep_qual, forall a. a -> a
id, Channel -> Backend
midi_channel Channel
1)
]
where
umbang :: Instrument
umbang = Text -> Instrument
inst forall a b. (a -> b) -> a -> b
$ Text
base forall a. Semigroup a => a -> a -> a
<> case Verbosity
verbosity of
Verbosity
Long -> Text
"-umbang"
Verbosity
Short -> Text
"u"
isep :: Instrument
isep = Text -> Instrument
inst forall a b. (a -> b) -> a -> b
$ Text
base forall a. Semigroup a => a -> a -> a
<> case Verbosity
verbosity of
Verbosity
Long -> Text
"-isep"
Verbosity
Short -> Text
"i"
pasang :: Config -> Config
pasang = Tuning -> Instrument -> Instrument -> Config -> Config
make_pasang Tuning
polos_tuning Instrument
umbang Instrument
isep
midi_channel :: Channel -> Backend
midi_channel Channel
relative_chan =
Config -> Backend
UiConfig.Midi (WriteDevice -> Channel -> Config
MidiInst.config1 WriteDevice
dev (Channel
chan forall a. Num a => a -> a -> a
+ Channel
relative_chan))
inst :: Text -> Instrument
inst = Text -> Instrument
ScoreT.Instrument
make_pasang :: BaliScales.Tuning -> ScoreT.Instrument -> ScoreT.Instrument
-> Common.Config -> Common.Config
make_pasang :: Tuning -> Instrument -> Instrument -> Config -> Config
make_pasang Tuning
polos_tuning Instrument
umbang Instrument
isep =
forall a. ToVal a => Text -> a -> Config -> Config
Common.add_cenviron Text
Gangsa.inst_polos Instrument
polos
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToVal a => Text -> a -> Config -> Config
Common.add_cenviron Text
Gangsa.inst_sangsih Instrument
sangsih
where
(Instrument
polos, Instrument
sangsih) = case Tuning
polos_tuning of
Tuning
BaliScales.Umbang -> (Instrument
umbang, Instrument
isep)
Tuning
BaliScales.Isep -> (Instrument
isep, Instrument
umbang)
type Device = Text
kebyar :: Device -> UiConfig.Allocations
kebyar :: Text -> Allocations
kebyar = Text -> Allocations
ScGamelan.kebyar_allocations
kendang_kontakt :: Device -> UiConfig.Allocations
kendang_kontakt :: Text -> Allocations
kendang_kontakt = Text -> Text -> Allocations
KendangBali.allocations Text
"k"
kendang_im :: UiConfig.Allocations
kendang_im :: Allocations
kendang_im = Text -> Allocations
Sampler.Patch.KendangBali.allocations Text
"k"
legong_umbang :: Patch.Scale
legong_umbang :: Scale
legong_umbang = Laras -> Tuning -> Scale
Legong.complete_instrument_scale Laras
Legong.laras_rambat
Tuning
BaliScales.Umbang
legong_isep :: Patch.Scale
legong_isep :: Scale
legong_isep = Laras -> Tuning -> Scale
Legong.complete_instrument_scale Laras
Legong.laras_rambat
Tuning
BaliScales.Isep