-- |
-- Module      :  DobutokO.Sound.Effects.Classes.FstParamSet
-- 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.FstParamSet 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.Channels
import DobutokO.Sound.Effects.Chorus
import DobutokO.Sound.Effects.Contrast
import DobutokO.Sound.Effects.DCShift
import DobutokO.Sound.Effects.Delay
import DobutokO.Sound.Effects.Dither
import DobutokO.Sound.Effects.Downsample
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.Hilbert
import DobutokO.Sound.Effects.LADSPA
import DobutokO.Sound.Effects.Loudness
import DobutokO.Sound.Effects.MCompand
import DobutokO.Sound.Effects.Misc
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.Repeat
import DobutokO.Sound.Effects.Reverb
import DobutokO.Sound.Effects.Segment
import DobutokO.Sound.Effects.Silence
import DobutokO.Sound.Effects.Sinc
import DobutokO.Sound.Effects.Specs
import DobutokO.Sound.Effects.Spectrogram
import DobutokO.Sound.Effects.Speed
import DobutokO.Sound.Effects.Splice
import DobutokO.Sound.Effects.Stat
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.Trim
import DobutokO.Sound.Effects.Upsample
import DobutokO.Sound.Effects.Vad
import DobutokO.Sound.Effects.Vol
import DobutokO.Sound.One

class FstParamSet a b where
  set1 :: a -> b
  set1G :: a -> b -> b
  set1G a
x = b -> b -> b
forall a. a -> a -> a
asTypeOf (a -> b
forall a b. FstParamSet a b => a -> b
set1 a
x)

class FstParamSet3 a b where
  set13 :: a -> b -> b
    
class FstParamSetL a b where
  set1L :: [a] -> b
  set1GL :: [a] -> b -> b
  set1GL [a]
xs = b -> b -> b
forall a. a -> a -> a
asTypeOf ([a] -> b
forall a b. FstParamSetL a b => [a] -> b
set1L [a]
xs)

class FstParamSetL3 a b where
  set13L :: [a] -> b -> b

class FstParamSet3O a b where
  set1o :: (One2 a) -> b -> b
  
instance FstParamSet3 a (FreqWidthS a b) where
  set13 :: a -> FreqWidthS a b -> FreqWidthS a b
set13 = a -> FreqWidthS a b -> FreqWidthS a b
forall a b. a -> FreqWidthS a b -> FreqWidthS a b
freqWidthSSet1

instance FstParamSet3 a (Bass a b) where
  set13 :: a -> Bass a b -> Bass a b
set13 = a -> Bass a b -> Bass a b
forall a b. a -> Bass a b -> Bass a b
bassSet1

instance FstParamSet3 a (Treble a b) where
  set13 :: a -> Treble a b -> Treble a b
set13 = a -> Treble a b -> Treble a b
forall a b. a -> Treble a b -> Treble a b
trebleSet1

instance FstParamSet3 a (BendTrio a b) where
  set13 :: a -> BendTrio a b -> BendTrio a b
set13 = a -> BendTrio a b -> BendTrio a b
forall a b. a -> BendTrio a b -> BendTrio a b
bendTrioSet1

instance FstParamSet a (FrameRate a) where 
  set1 :: a -> FrameRate a
set1 = a -> FrameRate a
forall a. a -> FrameRate a
frameRateSet1

instance FstParamSet a (OverSample a) where 
  set1 :: a -> OverSample a
set1 = a -> OverSample a
forall a. a -> OverSample a
overSampleSet1

instance FstParamSet3 a (Bend a b c) where
  set13 :: a -> Bend a b c -> Bend a b c
set13 = a -> Bend a b c -> Bend a b c
forall a b c. a -> Bend a b c -> Bend a b c
bendSet1

instance FstParamSet3 a (Coeffs a) where
  set13 :: a -> Coeffs a -> Coeffs a
set13 = a -> Coeffs a -> Coeffs a
forall a. a -> Coeffs a -> Coeffs a
coeffsSet1

instance FstParamSet3 (Coeffs a) (Biquad a) where
  set13 :: Coeffs a -> Biquad a -> Biquad a
set13 = Coeffs a -> Biquad a -> Biquad a
forall a. Coeffs a -> Biquad a -> Biquad a
biquadSet1

instance FstParamSet a (Chans a) where
  set1 :: a -> Chans a
set1 = a -> Chans a
forall a. a -> Chans a
channelsSet1

instance FstParamSet3 a (ChorusTail a b) where
  set13 :: a -> ChorusTail a b -> ChorusTail a b
set13 = Int -> a -> ChorusTail a b -> ChorusTail a b
forall a b. Int -> a -> ChorusTail a b -> ChorusTail a b
chorusTailSet1 Int
1  

instance FstParamSet3 a (Chorus a b) where
  set13 :: a -> Chorus a b -> Chorus a b
set13 = Int -> a -> Chorus a b -> Chorus a b
forall a b. Int -> a -> Chorus a b -> Chorus a b
chorusSet1 Int
1

instance FstParamSet3 a (Contrast a) where
  set13 :: a -> Contrast a -> Contrast a
set13 = a -> Contrast a -> Contrast a
forall a. a -> Contrast a -> Contrast a
contrastSet1
    
instance FstParamSet3 a (DCShift a b) where
  set13 :: a -> DCShift a b -> DCShift a b
set13 = a -> DCShift a b -> DCShift a b
forall a b. a -> DCShift a b -> DCShift a b
dcShiftSet1

instance FstParamSetL TSpecification Dlay where
  set1L :: [TSpecification] -> Dlay
set1L = [TSpecification] -> Dlay
delaySet1

instance FstParamSet a (Filter a) where
  set1 :: a -> Filter a
set1 = a -> Filter a
forall a. a -> Filter a
filterSet1

instance FstParamSet Float Precision where 
  set1 :: Float -> Precision
set1 = Float -> Precision
precisionSet1

instance FstParamSet3 a (Dither a b c) where 
  set13 :: a -> Dither a b c -> Dither a b c
set13 = a -> Dither a b c -> Dither a b c
forall a b c. a -> Dither a b c -> Dither a b c
ditherSet1

instance FstParamSet a (Downsample a) where
  set1 :: a -> Downsample a
set1 = a -> Downsample a
forall a. a -> Downsample a
downSampleSet1

instance FstParamSet3 a (EchoTail a) where
  set13 :: a -> EchoTail a -> EchoTail a
set13 = Int -> a -> EchoTail a -> EchoTail a
forall a. Int -> a -> EchoTail a -> EchoTail a
echoTailSet1 Int
1  

instance FstParamSet3 a (Echo a b) where
  set13 :: a -> Echo a b -> Echo a b
set13 = Int -> a -> Echo a b -> Echo a b
forall a b. Int -> a -> Echo a b -> Echo a b
echoSet1 Int
1

instance FstParamSet3 a (Echos a b) where
  set13 :: a -> Echos a b -> Echos a b
set13 = Int -> a -> Echos a b -> Echos a b
forall a b. Int -> a -> Echos a b -> Echos a b
echosSet1 Int
1  

instance FstParamSet3 a (Fade2 a b) where
  set13 :: a -> Fade2 a b -> Fade2 a b
set13 = a -> Fade2 a b -> Fade2 a b
forall a b. a -> Fade2 a b -> Fade2 a b
fadeSet1

instance FstParamSet3 String Fade where
  set13 :: String -> Fade -> Fade
set13 = Int -> String -> Fade -> Fade
fadeSet2E Int
1  

instance FstParamSet a (Fir a b) where
  set1 :: a -> Fir a b
set1 = a -> Fir a b
forall a b. a -> Fir a b
firSet1

instance FstParamSetL3 a (Flanger a b) where 
  set13L :: [a] -> Flanger a b -> Flanger a b
set13L = [a] -> Flanger a b -> Flanger a b
forall a b. [a] -> Flanger a b -> Flanger a b
flangerSet1
  
instance FstParamSet3 a (Gain1 a b c d) where
  set13 :: a -> Gain1 a b c d -> Gain1 a b c d
set13 = a -> Gain1 a b c d -> Gain1 a b c d
forall a b c d. a -> Gain1 a b c d -> Gain1 a b c d
gainSet1

instance FstParamSet a (Hilbert a) where
  set1 :: a -> Hilbert a
set1 = a -> Hilbert a
forall a. a -> Hilbert a
HI

instance FstParamSet3 a (Ladspa1 a b c) where
  set13 :: a -> Ladspa1 a b c -> Ladspa1 a b c
set13 = a -> Ladspa1 a b c -> Ladspa1 a b c
forall a b c. a -> Ladspa1 a b c -> Ladspa1 a b c
ladspaSet1

instance FstParamSet3 a (Loudness a) where
  set13 :: a -> Loudness a -> Loudness a
set13 = a -> Loudness a -> Loudness a
forall a. a -> Loudness a -> Loudness a
loudnessSet1

instance FstParamSet a (FloatE a) where
  set1 :: a -> FloatE a
set1 = a -> FloatE a
forall a. a -> FloatE a
floatESet1

instance FstParamSet3O a (CompandTail a b) where 
  set1o :: One2 a -> CompandTail a b -> CompandTail a b
set1o = One2 a -> CompandTail a b -> CompandTail a b
forall a b. One2 a -> CompandTail a b -> CompandTail a b
compandTailSet1

instance FstParamSet3 a (Pair a) where 
  set13 :: a -> Pair a -> Pair a
set13 = a -> Pair a -> Pair a
forall a. a -> Pair a -> Pair a
pairSet1

instance FstParamSet3 a (AtDe a) where
  set13 :: a -> AtDe a -> AtDe a
set13 = a -> AtDe a -> AtDe a
forall a. a -> AtDe a -> AtDe a
atDeSet1

instance FstParamSet a (Neg a) where
  set1 :: a -> Neg a
set1 = a -> Neg a
forall a. a -> Neg a
NG

instance FstParamSet a (SoftKnee a) where
  set1 :: a -> SoftKnee a
set1 = a -> SoftKnee a
forall a. a -> SoftKnee a
SK

instance FstParamSet3 a (Compand a b c d) where
  set13 :: a -> Compand a b c d -> Compand a b c d
set13 = a -> Compand a b c d -> Compand a b c d
forall a b c d. a -> Compand a b c d -> Compand a b c d
compandSet1
    
instance FstParamSet3 a (FreqComp a b) where
  set13 :: a -> FreqComp a b -> FreqComp a b
set13 = a -> FreqComp a b -> FreqComp a b
forall a b. a -> FreqComp a b -> FreqComp a b
freqCompSet1

instance FstParamSet3 a (MCompand a b) where
  set13 :: a -> MCompand a b -> MCompand a b
set13 = a -> MCompand a b -> MCompand a b
forall a b. a -> MCompand a b -> MCompand a b
mCompandSet1

instance FstParamSetL a (MscS a) where
  set1L :: [a] -> MscS a
set1L = [a] -> MscS a
forall a. [a] -> MscS a
mscSSet1

instance FstParamSet a (Noiseprof a) where
  set1 :: a -> Noiseprof a
set1 = a -> Noiseprof a
forall a. a -> Noiseprof a
noiseprofSet1

instance FstParamSet3 a (Noisered a b) where 
  set13 :: a -> Noisered a b -> Noisered a b
set13 = a -> Noisered a b -> Noisered a b
forall a b. a -> Noisered a b -> Noisered a b
noiseredSet1

instance FstParamSet3 a (Overdrive a) where 
  set13 :: a -> Overdrive a -> Overdrive a
set13 = a -> Overdrive a -> Overdrive a
forall a. a -> Overdrive a -> Overdrive a
overdriveSet1

instance FstParamSet3 a (PadSpec a) where
  set13 :: a -> PadSpec a -> PadSpec a
set13 = a -> PadSpec a -> PadSpec a
forall a. a -> PadSpec a -> PadSpec a
padSpecSet1

instance FstParamSet3O a (Pad a b) where
  set1o :: One2 a -> Pad a b -> Pad a b
set1o = One2 a -> Pad a b -> Pad a b
forall a b. One2 a -> Pad a b -> Pad a b
padSet1

instance FstParamSet3 a (FreqWidth a b) where
  set13 :: a -> FreqWidth a b -> FreqWidth a b
set13 = a -> FreqWidth a b -> FreqWidth a b
forall a b. a -> FreqWidth a b -> FreqWidth a b
freqWidthSet1

instance FstParamSet3 a (Freq a) where
  set13 :: a -> Freq a -> Freq a
set13 = a -> Freq a -> Freq a
forall a. a -> Freq a -> Freq a
freqSet1

instance FstParamSet3 a (AllPass a) where 
  set13 :: a -> AllPass a -> AllPass a
set13 = a -> AllPass a -> AllPass a
forall a. a -> AllPass a -> AllPass a
allPassSet1

instance FstParamSet3 a (BandReject a) where
  set13 :: a -> BandReject a -> BandReject a
set13 = a -> BandReject a -> BandReject a
forall a. a -> BandReject a -> BandReject a
bandRejectSet1
  
instance FstParamSet3 a (BandPass a b) where
  set13 :: a -> BandPass a b -> BandPass a b
set13 = a -> BandPass a b -> BandPass a b
forall a b. a -> BandPass a b -> BandPass a b
bandPassSet1

instance FstParamSet3 a (Band a b) where
  set13 :: a -> Band a b -> Band a b
set13 = a -> Band a b -> Band a b
forall a b. a -> Band a b -> Band a b
bandSet1

instance FstParamSet3 a (HighPass a b) where
  set13 :: a -> HighPass a b -> HighPass a b
set13 = a -> HighPass a b -> HighPass a b
forall a b. a -> HighPass a b -> HighPass a b
highPassSet1

instance FstParamSet3 a (LowPass a b) where
  set13 :: a -> LowPass a b -> LowPass a b
set13 = a -> LowPass a b -> LowPass a b
forall a b. a -> LowPass a b -> LowPass a b
lowPassSet1

instance FstParamSet3 a (Equalizer a b) where
  set13 :: a -> Equalizer a b -> Equalizer a b
set13 = a -> Equalizer a b -> Equalizer a b
forall a b. a -> Equalizer a b -> Equalizer a b
equalizerSet1

instance FstParamSet3 a (Phaser a b) where
  set13 :: a -> Phaser a b -> Phaser a b
set13 = Int -> a -> Phaser a b -> Phaser a b
forall a b. Int -> a -> Phaser a b -> Phaser a b
phaserSet1 Int
1

instance FstParamSet3 a (Pitch a b c) where 
  set13 :: a -> Pitch a b c -> Pitch a b c
set13 = a -> Pitch a b c -> Pitch a b c
forall a b c. a -> Pitch a b c -> Pitch a b c
pitchSet1

instance FstParamSet a (Ropt4 a) where 
  set1 :: a -> Ropt4 a
set1 = a -> Ropt4 a
forall a. a -> Ropt4 a
rOpt4Set1

instance FstParamSet a (Ropt5 a) where
  set1 :: a -> Ropt5 a
set1 = a -> Ropt5 a
forall a. a -> Ropt5 a
rOpt5Set1

instance FstParamSet3 a (RateL a b) where
  set13 :: a -> RateL a b -> RateL a b
set13 = a -> RateL a b -> RateL a b
forall a b. a -> RateL a b -> RateL a b
rateLSet1

instance FstParamSet3 a (RateH a b1 b2 b3 b4 b5 c) where
  set13 :: a -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
set13 = a -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
forall a b1 b2 b3 b4 b5 c.
a -> RateH a b1 b2 b3 b4 b5 c -> RateH a b1 b2 b3 b4 b5 c
rateHSet1

instance FstParamSet RateLow Rate where
  set1 :: RateLow -> Rate
set1 = RateLow -> Rate
rate2Set1
    
instance FstParamSet3 Float (Vol3 Float) where
  set13 :: Float -> Vol3 Float -> Vol3 Float
set13 = Float -> Vol3 Float -> Vol3 Float
vol3Set1

instance FstParamSet3 a (IChannel a b) where
  set13 :: a -> IChannel a b -> IChannel a b
set13 = a -> IChannel a b -> IChannel a b
forall a b. a -> IChannel a b -> IChannel a b
ichannelSet1

instance FstParamSetL3 a (OChannel a) where
  set13L :: [a] -> OChannel a -> OChannel a
set13L = [a] -> OChannel a -> OChannel a
forall a. [a] -> OChannel a -> OChannel a
ochannelSet1

instance FstParamSet3 MixSpec ReMix where
  set13 :: MixSpec -> ReMix -> ReMix
set13 = MixSpec -> ReMix -> ReMix
remixSet1

instance FstParamSet a (Repeat a) where 
  set1 :: a -> Repeat a
set1 = a -> Repeat a
forall a. a -> Repeat a
Rpt

instance FstParamSet3 a (Reverb a b c d) where 
  set13 :: a -> Reverb a b c d -> Reverb a b c d
set13 = a -> Reverb a b c d -> Reverb a b c d
forall a b c d. a -> Reverb a b c d -> Reverb a b c d
reverbSet1

instance FstParamSet3 Float ReverbE where
  set13 :: Float -> ReverbE -> ReverbE
set13 = Int -> Float -> ReverbE -> ReverbE
reverbSet3E Int
1  

instance FstParamSet3 a (Segment a) where
  set13 :: a -> Segment a -> Segment a
set13 = a -> Segment a -> Segment a
forall a. a -> Segment a -> Segment a
segmentSet1

instance FstParamSet3 a (Threshold a) where
  set13 :: a -> Threshold a -> Threshold a
set13 = a -> Threshold a -> Threshold a
forall a. a -> Threshold a -> Threshold a
thresholdSet1

instance FstParamSet3 a (Duration a b) where
  set13 :: a -> Duration a b -> Duration a b
set13 = a -> Duration a b -> Duration a b
forall a b. a -> Duration a b -> Duration a b
durationSet1d

instance FstParamSet3 a (AboveTSpec1 a b c) where
  set13 :: a -> AboveTSpec1 a b c -> AboveTSpec1 a b c
set13 = a -> AboveTSpec1 a b c -> AboveTSpec1 a b c
forall a b c. a -> AboveTSpec1 a b c -> AboveTSpec1 a b c
aboveTSpecSet1a

instance FstParamSet3 a (BelowTSpec1 a b c) where 
  set13 :: a -> BelowTSpec1 a b c -> BelowTSpec1 a b c
set13 = a -> BelowTSpec1 a b c -> BelowTSpec1 a b c
forall a b c. a -> BelowTSpec1 a b c -> BelowTSpec1 a b c
belowTSpecSet1b

instance FstParamSet3 a (Silence a b c) where
  set13 :: a -> Silence a b c -> Silence a b c
set13 = a -> Silence a b c -> Silence a b c
forall a b c. a -> Silence a b c -> Silence a b c
silenceSet1
  
instance FstParamSet a (PhaseR a) where
  set1 :: a -> PhaseR a
set1 = a -> PhaseR a
forall a. a -> PhaseR a
phaseRSet1

instance FstParamSet a (FreqL a) where
  set1 :: a -> FreqL a
set1 = a -> FreqL a
forall a. a -> FreqL a
freqLSet1

instance FstParamSet a (FreqH a) where
  set1 :: a -> FreqH a
set1 = a -> FreqH a
forall a. a -> FreqH a
freqHSet1

instance FstParamSet3 a (Sinc a b c d) where 
  set13 :: a -> Sinc a b c d -> Sinc a b c d
set13 = a -> Sinc a b c d -> Sinc a b c d
forall a b c d. a -> Sinc a b c d -> Sinc a b c d
sincSet1

instance FstParamSet3 Float Freq1 where 
  set13 :: Float -> Freq1 -> Freq1
set13 = Float -> Freq1 -> Freq1
frequencySet1

instance FstParamSet3 a (Width a) where
  set13 :: a -> Width a -> Width a
set13 = a -> Width a -> Width a
forall a. a -> Width a -> Width a
widthSet1

instance FstParamSet3 a (SFloat1 a) where
  set13 :: a -> SFloat1 a -> SFloat1 a
set13 = a -> SFloat1 a -> SFloat1 a
forall a. a -> SFloat1 a -> SFloat1 a
sFloat1Set1

instance FstParamSet3 a (SString1 a) where
  set13 :: a -> SString1 a -> SString1 a
set13 = a -> SString1 a -> SString1 a
forall a. a -> SString1 a -> SString1 a
sString1Set1

instance FstParamSet a (Advanced1 a) where
  set1 :: a -> Advanced1 a
set1 = a -> Advanced1 a
forall a. a -> Advanced1 a
advanced1Set1

instance FstParamSet Float FirstDTSpec where
  set1 :: Float -> FirstDTSpec
set1 = Float -> FirstDTSpec
seconds2FstDTSpec2
    
instance FstParamSet Int FirstDTSpec where
  set1 :: Int -> FirstDTSpec
set1 = Int -> FirstDTSpec
samples2FstDTSpec2

instance FstParamSetL3 a (Spectrogram3 a b c d e) where
  set13L :: [a] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
set13L = [a] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
forall a b c d e.
[a] -> Spectrogram3 a b c d e -> Spectrogram3 a b c d e
spectrogramSet31

instance FstParamSet3 a (Speed a b) where
  set13 :: a -> Speed a b -> Speed a b
set13 = a -> Speed a b -> Speed a b
forall a b. a -> Speed a b -> Speed a b
speedSet1

instance FstParamSet3 a (Splice2 a b) where
  set13 :: a -> Splice2 a b -> Splice2 a b
set13 = a -> Splice2 a b -> Splice2 a b
forall a b. a -> Splice2 a b -> Splice2 a b
splice2Set1

instance FstParamSet a (StatP a) where
  set1 :: a -> StatP a
set1 = a -> StatP a
forall a. a -> StatP a
statPSet1

instance FstParamSetL a (Stat1 a) where 
  set1L :: [a] -> Stat1 a
set1L = [a] -> Stat1 a
forall a. [a] -> Stat1 a
stat1Set1

instance FstParamSet3 a (StatsP a) where 
  set13 :: a -> StatsP a -> StatsP a
set13 = a -> StatsP a -> StatsP a
forall a. a -> StatsP a -> StatsP a
statsPSet1

instance FstParamSet a (Window1 a) where
  set1 :: a -> Window1 a
set1 = a -> Window1 a
forall a. a -> Window1 a
window1Set1

instance FstParamSetL3 a (Stats2 a b) where
  set13L :: [a] -> Stats2 a b -> Stats2 a b
set13L = [a] -> Stats2 a b -> Stats2 a b
forall a b. [a] -> Stats2 a b -> Stats2 a b
stats2Set1

instance FstParamSet3 a (StretchP a) where
  set13 :: a -> StretchP a -> StretchP a
set13 = a -> StretchP a -> StretchP a
forall a. a -> StretchP a -> StretchP a
stretchSet1

instance FstParamSet3 a (Stretch2 a b) where
  set13 :: a -> Stretch2 a b -> Stretch2 a b
set13 = a -> Stretch2 a b -> Stretch2 a b
forall a b. a -> Stretch2 a b -> Stretch2 a b
stretch2Set1

instance FstParamSet3 a (Tempo a b c d) where 
  set13 :: a -> Tempo a b c d -> Tempo a b c d
set13 = a -> Tempo a b c d -> Tempo a b c d
forall a b c d. a -> Tempo a b c d -> Tempo a b c d
tempoSet1

instance FstParamSet3 a (TimeSpec a b) where
  set13 :: a -> TimeSpec a b -> TimeSpec a b
set13 = a -> TimeSpec a b -> TimeSpec a b
forall a b. a -> TimeSpec a b -> TimeSpec a b
timeSpecSet1

instance FstParamSet3 a (Tremolo a) where
  set13 :: a -> Tremolo a -> Tremolo a
set13 = a -> Tremolo a -> Tremolo a
forall a. a -> Tremolo a -> Tremolo a
tremoloSet1

instance FstParamSet a (Trim a) where 
  set1 :: a -> Trim a
set1 = a -> Trim a
forall a. a -> Trim a
trimSet1

instance FstParamSet a (Upsample a) where 
  set1 :: a -> Upsample a
set1 = a -> Upsample a
forall a. a -> Upsample a
upSampleSet1

instance FstParamSet3 a (VadP a) where
  set13 :: a -> VadP a -> VadP a
set13 = a -> VadP a -> VadP a
forall a. a -> VadP a -> VadP a
vadPSet1

instance FstParamSetL3 a (Vad1 a) where
  set13L :: [a] -> Vad1 a -> Vad1 a
set13L = [a] -> Vad1 a -> Vad1 a
forall a. [a] -> Vad1 a -> Vad1 a
vad1Set1

instance FstParamSet3 a (Vol2 a b) where
  set13 :: a -> Vol2 a b -> Vol2 a b
set13 = a -> Vol2 a b -> Vol2 a b
forall a b. a -> Vol2 a b -> Vol2 a b
volSet1

instance FstParamSet3 a (One2 a) where
  set13 :: a -> One2 a -> One2 a
set13 = a -> One2 a -> One2 a
forall a. a -> One2 a -> One2 a
one2Set1

instance FstParamSet3 a (One3 a) where
  set13 :: a -> One3 a -> One3 a
set13 = a -> One3 a -> One3 a
forall a. a -> One3 a -> One3 a
one3Set1

------------------------------------------------------------------------------------------