-- |
-- Module      :  DobutokO.Sound.Effects.Classes.SndParamSet
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Helps to create experimental music. 
-- Can be used for applying the SoX effects. 
-- 

{-# OPTIONS_GHC -threaded #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

module DobutokO.Sound.Effects.Classes.SndParamSet where

-- inspired with: https://wiki.haskell.org/Scoped_type_variables
import GHC.Base (asTypeOf)
import DobutokO.Sound.Effects.BassTreble
import DobutokO.Sound.Effects.Bend
import DobutokO.Sound.Effects.Biquad
import DobutokO.Sound.Effects.Chorus
import DobutokO.Sound.Effects.DCShift
import DobutokO.Sound.Effects.Dither
import DobutokO.Sound.Effects.Echo
import DobutokO.Sound.Effects.Fade
import DobutokO.Sound.Effects.FIR
import DobutokO.Sound.Effects.Flanger
import DobutokO.Sound.Effects.Gain
import DobutokO.Sound.Effects.LADSPA
import DobutokO.Sound.Effects.Loudness
import DobutokO.Sound.Effects.MCompand
import DobutokO.Sound.Effects.Noise
import DobutokO.Sound.Effects.Overdrive
import DobutokO.Sound.Effects.Pad
import DobutokO.Sound.Effects.PassReject
import DobutokO.Sound.Effects.Phaser
import DobutokO.Sound.Effects.Pitch
import DobutokO.Sound.Effects.Rate
import DobutokO.Sound.Effects.Remix
import DobutokO.Sound.Effects.Reverb
import DobutokO.Sound.Effects.Silence
import DobutokO.Sound.Effects.Sinc
import DobutokO.Sound.Effects.Spectrogram
import DobutokO.Sound.Effects.Speed
import DobutokO.Sound.Effects.Splice
import DobutokO.Sound.Effects.Stats
import DobutokO.Sound.Effects.Stretch
import DobutokO.Sound.Effects.Tempo
import DobutokO.Sound.Effects.Timespec
import DobutokO.Sound.Effects.Tremolo
import DobutokO.Sound.Effects.Vol
import DobutokO.Sound.One

class SndParamSet a b where
  set2 :: a -> b
  set2G :: a -> b -> b
  set2G a
x = b -> b -> b
forall a. a -> a -> a
asTypeOf (a -> b
forall a b. SndParamSet a b => a -> b
set2 a
x)

class SndParamSet3 a b where
  set23 :: a -> b -> b
    
class SndParamSet3M a b where
  set23m :: a -> b -> Maybe b 
     
class SndParamSetL a b where
  set2L :: [a] -> b
  set2GL :: [a] -> b -> b
  set2GL [a]
xs = b -> b -> b
forall a. a -> a -> a
asTypeOf ([a] -> b
forall a b. SndParamSetL a b => [a] -> b
set2L [a]
xs)

class SndParamSetL3 a b where
  set23L :: [a] -> b -> b

class SndParamSet3O a b where
  set23o :: (One2 a) -> b -> b

instance SndParamSet3 b (FreqWidthS a b) where
  set23 :: b -> FreqWidthS a b -> FreqWidthS a b
set23 = b -> FreqWidthS a b -> FreqWidthS a b
forall b a. b -> FreqWidthS a b -> FreqWidthS a b
freqWidthSSet2

instance SndParamSet3 b (Bass a b) where
  set23 :: b -> Bass a b -> Bass a b
set23 = b -> Bass a b -> Bass a b
forall b a. b -> Bass a b -> Bass a b
bassSet2

instance SndParamSet3 b (Treble a b) where
  set23 :: b -> Treble a b -> Treble a b
set23 = b -> Treble a b -> Treble a b
forall b a. b -> Treble a b -> Treble a b
trebleSet2

instance SndParamSet3 b (BendTrio a b) where
  set23 :: b -> BendTrio a b -> BendTrio a b
set23 = b -> BendTrio a b -> BendTrio a b
forall b a. b -> BendTrio a b -> BendTrio a b
bendTrioSet2

instance SndParamSet3 b (Bend a b c) where
  set23 :: b -> Bend a b c -> Bend a b c
set23 = b -> Bend a b c -> Bend a b c
forall b a c. b -> Bend a b c -> Bend a b c
bendSet2

instance SndParamSet3 a (Coeffs a)  where
  set23 :: a -> Coeffs a -> Coeffs a
set23 = a -> Coeffs a -> Coeffs a
forall a. a -> Coeffs a -> Coeffs a
coeffsSet2 

instance SndParamSet3 (Coeffs a) (Biquad a) where
  set23 :: Coeffs a -> Biquad a -> Biquad a
set23 = Coeffs a -> Biquad a -> Biquad a
forall a. Coeffs a -> Biquad a -> Biquad a
biquadSet2

instance SndParamSet3 a (ChorusTail a b)  where
  set23 :: a -> ChorusTail a b -> ChorusTail a b
set23 = Int -> a -> ChorusTail a b -> ChorusTail a b
forall a b. Int -> a -> ChorusTail a b -> ChorusTail a b
chorusTailSet1 Int
2

instance SndParamSet3 a (Chorus a b)  where
  set23 :: a -> Chorus a b -> Chorus a b
set23 = Int -> a -> Chorus a b -> Chorus a b
forall a b. Int -> a -> Chorus a b -> Chorus a b
chorusSet1 Int
2  

instance SndParamSet3 b (DCShift a b) where
  set23 :: b -> DCShift a b -> DCShift a b
set23 = b -> DCShift a b -> DCShift a b
forall b a. b -> DCShift a b -> DCShift a b
dcShiftSet2

instance SndParamSet3 b (Dither a b c) where 
  set23 :: b -> Dither a b c -> Dither a b c
set23 = b -> Dither a b c -> Dither a b c
forall b a c. b -> Dither a b c -> Dither a b c
ditherSet2

instance SndParamSet3 a (EchoTail a)  where
  set23 :: a -> EchoTail a -> EchoTail a
set23 = Int -> a -> EchoTail a -> EchoTail a
forall a. Int -> a -> EchoTail a -> EchoTail a
echoTailSet1 Int
2 

instance SndParamSet3 a (Echo a b)  where
  set23 :: a -> Echo a b -> Echo a b
set23 = Int -> a -> Echo a b -> Echo a b
forall a b. Int -> a -> Echo a b -> Echo a b
echoSet1 Int
2

instance SndParamSet3 a (Echos a b)  where
  set23 :: a -> Echos a b -> Echos a b
set23 = Int -> a -> Echos a b -> Echos a b
forall a b. Int -> a -> Echos a b -> Echos a b
echosSet1 Int
2

instance SndParamSetL3 b (Fade2 a b) where
  set23L :: [b] -> Fade2 a b -> Fade2 a b
set23L = [b] -> Fade2 a b -> Fade2 a b
forall b a. [b] -> Fade2 a b -> Fade2 a b
fadeSet2

instance SndParamSet3 String Fade where
  set23 :: String -> Fade -> Fade
set23 = Int -> String -> Fade -> Fade
fadeSet2E Int
2

instance SndParamSetL b (Fir a b) where
  set2L :: [b] -> Fir a b
set2L = [b] -> Fir a b
forall b a. [b] -> Fir a b
firSet2

instance SndParamSet3 b (Flanger a b) where 
  set23 :: b -> Flanger a b -> Flanger a b
set23 = b -> Flanger a b -> Flanger a b
forall b a. b -> Flanger a b -> Flanger a b
flangerSet2

instance SndParamSet3 b (Gain1 a b c d) where
  set23 :: b -> Gain1 a b c d -> Gain1 a b c d
set23 = b -> Gain1 a b c d -> Gain1 a b c d
forall b a c d. b -> Gain1 a b c d -> Gain1 a b c d
gainSet2

instance SndParamSet3O b (Ladspa1 a b c) where
  set23o :: One2 b -> Ladspa1 a b c -> Ladspa1 a b c
set23o = One2 b -> Ladspa1 a b c -> Ladspa1 a b c
forall b a c. One2 b -> Ladspa1 a b c -> Ladspa1 a b c
ladspaSet2

instance SndParamSet3 a (Loudness a)  where
  set23 :: a -> Loudness a -> Loudness a
set23 = a -> Loudness a -> Loudness a
forall a. a -> Loudness a -> Loudness a
loudnessSet2

instance SndParamSet3M b (CompandTail a b) where 
  set23m :: b -> CompandTail a b -> Maybe (CompandTail a b)
set23m = b -> CompandTail a b -> Maybe (CompandTail a b)
forall b a. b -> CompandTail a b -> Maybe (CompandTail a b)
compandTailSet2

instance SndParamSet3 a (Pair a)  where 
  set23 :: a -> Pair a -> Pair a
set23 = a -> Pair a -> Pair a
forall a. a -> Pair a -> Pair a
pairSet2

instance SndParamSetL3 a (AtDe a)  where
  set23L :: [a] -> AtDe a -> AtDe a
set23L = [a] -> AtDe a -> AtDe a
forall a. [a] -> AtDe a -> AtDe a
atDeSet2

instance SndParamSet3 b (Compand a b c d) where
  set23 :: b -> Compand a b c d -> Compand a b c d
set23 = b -> Compand a b c d -> Compand a b c d
forall b a c d. b -> Compand a b c d -> Compand a b c d
compandSet2

instance SndParamSet3 b (FreqComp a b) where
  set23 :: b -> FreqComp a b -> FreqComp a b
set23 = b -> FreqComp a b -> FreqComp a b
forall b a. b -> FreqComp a b -> FreqComp a b
freqCompSet2

instance SndParamSetL3 b (MCompand a b) where
  set23L :: [b] -> MCompand a b -> MCompand a b
set23L = [b] -> MCompand a b -> MCompand a b
forall b a. [b] -> MCompand a b -> MCompand a b
mCompandSet2

instance SndParamSet3M b (Noisered a b) where 
  set23m :: b -> Noisered a b -> Maybe (Noisered a b)
set23m = b -> Noisered a b -> Maybe (Noisered a b)
forall b a. b -> Noisered a b -> Maybe (Noisered a b)
noiseredSet2

instance SndParamSet3M a (Overdrive a)  where 
  set23m :: a -> Overdrive a -> Maybe (Overdrive a)
set23m = a -> Overdrive a -> Maybe (Overdrive a)
forall a. a -> Overdrive a -> Maybe (Overdrive a)
overdriveSet2

instance SndParamSet3 a (PadSpec a)  where
  set23 :: a -> PadSpec a -> PadSpec a
set23 = a -> PadSpec a -> PadSpec a
forall a. a -> PadSpec a -> PadSpec a
padSpecSet2

instance SndParamSetL3 b (Pad a b) where
  set23L :: [b] -> Pad a b -> Pad a b
set23L = [b] -> Pad a b -> Pad a b
forall b a. [b] -> Pad a b -> Pad a b
padSet2

instance SndParamSet3 b (FreqWidth a b) where
  set23 :: b -> FreqWidth a b -> FreqWidth a b
set23 = b -> FreqWidth a b -> FreqWidth a b
forall b a. b -> FreqWidth a b -> FreqWidth a b
freqWidthSet2

instance SndParamSet3 b (BandPass a b) where
  set23 :: b -> BandPass a b -> BandPass a b
set23 = b -> BandPass a b -> BandPass a b
forall b a. b -> BandPass a b -> BandPass a b
bandPassSet2

instance SndParamSet3 b (Band a b) where
  set23 :: b -> Band a b -> Band a b
set23 = b -> Band a b -> Band a b
forall b a. b -> Band a b -> Band a b
bandSet2

instance SndParamSet3 b (HighPass a b) where
  set23 :: b -> HighPass a b -> HighPass a b
set23 = b -> HighPass a b -> HighPass a b
forall b a. b -> HighPass a b -> HighPass a b
highPassSet2

instance SndParamSet3 b (LowPass a b) where
  set23 :: b -> LowPass a b -> LowPass a b
set23 = b -> LowPass a b -> LowPass a b
forall b a. b -> LowPass a b -> LowPass a b
lowPassSet2

instance SndParamSet3 b (Equalizer a b) where
  set23 :: b -> Equalizer a b -> Equalizer a b
set23 = b -> Equalizer a b -> Equalizer a b
forall b a. b -> Equalizer a b -> Equalizer a b
equalizerSet2

instance SndParamSet3 a (Phaser a b)  where
  set23 :: a -> Phaser a b -> Phaser a b
set23 = Int -> a -> Phaser a b -> Phaser a b
forall a b. Int -> a -> Phaser a b -> Phaser a b
phaserSet1 Int
2

instance SndParamSet3 b (Pitch a b c) where 
  set23 :: b -> Pitch a b c -> Pitch a b c
set23 = b -> Pitch a b c -> Pitch a b c
forall b a c. b -> Pitch a b c -> Pitch a b c
pitchSet2

instance SndParamSet3 b (RateL a b) where
  set23 :: b -> RateL a b -> RateL a b
set23 = b -> RateL a b -> RateL a b
forall b a. b -> RateL a b -> RateL a b
rateLSet2

instance SndParamSet3 b1 (RateH a b1 b2 b3 b4 b5 c) where
  set23 :: b1 -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
set23 = b1 -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
forall b1 a b2 b3 b4 b5 c.
b1 -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
rateHSet21

instance SndParamSet RateHigh Rate where
  set2 :: RateHigh -> Rate
set2 = RateHigh -> Rate
rate2Set2

instance SndParamSet3 (Vol3 b) (IChannel a b) where
  set23 :: Vol3 b -> IChannel a b -> IChannel a b
set23 = Vol3 b -> IChannel a b -> IChannel a b
forall b a. Vol3 b -> IChannel a b -> IChannel a b
ichannelSet2
    
instance SndParamSetL3 OChanF ReMix where
  set23L :: [OChanF] -> ReMix -> ReMix
set23L = [OChanF] -> ReMix -> ReMix
remixSet2

instance SndParamSet3 b (Reverb a b c d) where 
  set23 :: b -> Reverb a b c d -> Reverb a b c d
set23 = b -> Reverb a b c d -> Reverb a b c d
forall b a c d. b -> Reverb a b c d -> Reverb a b c d
reverbSet2

instance SndParamSet3 Float ReverbE where
  set23 :: Float -> ReverbE -> ReverbE
set23 = Int -> Float -> ReverbE -> ReverbE
reverbSet3E Int
2  

instance SndParamSet3 b (Duration a b) where
  set23 :: b -> Duration a b -> Duration a b
set23 = b -> Duration a b -> Duration a b
forall b a. b -> Duration a b -> Duration a b
durationSet2d

instance SndParamSet3 b (AboveTSpec1 a b c) where
  set23 :: b -> AboveTSpec1 a b c -> AboveTSpec1 a b c
set23 = b -> AboveTSpec1 a b c -> AboveTSpec1 a b c
forall b a c. b -> AboveTSpec1 a b c -> AboveTSpec1 a b c
aboveTSpecSet2a

instance SndParamSet3 b (BelowTSpec1 a b c) where 
  set23 :: b -> BelowTSpec1 a b c -> BelowTSpec1 a b c
set23 = b -> BelowTSpec1 a b c -> BelowTSpec1 a b c
forall b a c. b -> BelowTSpec1 a b c -> BelowTSpec1 a b c
belowTSpecSet2b

instance SndParamSet3 b (Silence a b c) where
  set23 :: b -> Silence a b c -> Silence a b c
set23 = b -> Silence a b c -> Silence a b c
forall b a c. b -> Silence a b c -> Silence a b c
silenceSet2
  
instance SndParamSet3 b (Sinc a b c d) where 
  set23 :: b -> Sinc a b c d -> Sinc a b c d
set23 = b -> Sinc a b c d -> Sinc a b c d
forall b a c d. b -> Sinc a b c d -> Sinc a b c d
sincSet2
    
instance SndParamSetL3 b (Spectrogram3 a b c d e) where
  set23L :: [b] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
set23L = [b] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
forall b a c d e.
[b] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
spectrogramSet32

instance SndParamSet3 b (Speed a b) where
  set23 :: b -> Speed a b -> Speed a b
set23 = b -> Speed a b -> Speed a b
forall b a. b -> Speed a b -> Speed a b
speedSet2

instance SndParamSetL3 (One3 b) (Splice2 a b) where
  set23L :: [One3 b] -> Splice2 a b -> Splice2 a b
set23L = [One3 b] -> Splice2 a b -> Splice2 a b
forall b a. [One3 b] -> Splice2 a b -> Splice2 a b
splice2Set2

instance SndParamSetL3 b (Stats2 a b) where
  set23L :: [b] -> Stats2 a b -> Stats2 a b
set23L = [b] -> Stats2 a b -> Stats2 a b
forall b a. [b] -> Stats2 a b -> Stats2 a b
stats2Set2

instance SndParamSet3 a (StretchP a)  where
  set23 :: a -> StretchP a -> StretchP a
set23 = a -> StretchP a -> StretchP a
forall a. a -> StretchP a -> StretchP a
stretchSet2

instance SndParamSet3 b (Stretch2 a b) where
  set23 :: b -> Stretch2 a b -> Stretch2 a b
set23 = b -> Stretch2 a b -> Stretch2 a b
forall b a. b -> Stretch2 a b -> Stretch2 a b
stretch2Set2

instance SndParamSet3 b (Tempo a b c d) where 
  set23 :: b -> Tempo a b c d -> Tempo a b c d
set23 = b -> Tempo a b c d -> Tempo a b c d
forall b a c d. b -> Tempo a b c d -> Tempo a b c d
tempoSet2

instance SndParamSetL3 b (TimeSpec a b) where
  set23L :: [b] -> TimeSpec a b -> TimeSpec a b
set23L = [b] -> TimeSpec a b -> TimeSpec a b
forall b a. [b] -> TimeSpec a b -> TimeSpec a b
timeSpecSet2

instance SndParamSet3 a (Tremolo a)  where
  set23 :: a -> Tremolo a -> Tremolo a
set23 = a -> Tremolo a -> Tremolo a
forall a. a -> Tremolo a -> Tremolo a
tremoloSet2

instance SndParamSet3 b (Vol2 a b) where
  set23 :: b -> Vol2 a b -> Vol2 a b
set23 = b -> Vol2 a b -> Vol2 a b
forall b a. b -> Vol2 a b -> Vol2 a b
volSet2