-- |
-- Module      :  DobutokO.Sound.Effects.Classes.FstParam
-- 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.FstParam where

import DobutokO.Sound.Effects.Splice
import DobutokO.Sound.Effects.Vad
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.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.Vol
import DobutokO.Sound.One


class FstParam a b where
  get1 :: a -> b

class FstParamL a b where
  get1L :: a -> [b]

class FstParamM a b where
  get1m :: a -> Maybe b  
  
instance FstParam (FreqWidthS a b) a where
  get1 :: FreqWidthS a b -> a
get1 = FreqWidthS a b -> a
forall a b. FreqWidthS a b -> a
freqWidthS1

instance FstParam (Bass a b) a where
  get1 :: Bass a b -> a
get1 = Bass a b -> a
forall a b. Bass a b -> a
bass1

instance FstParam (Treble a b) a where
  get1 :: Treble a b -> a
get1 = Treble a b -> a
forall a b. Treble a b -> a
treble1

instance FstParam (BendTrio a b) a where
  get1 :: BendTrio a b -> a
get1 = BendTrio a b -> a
forall a b. BendTrio a b -> a
bendTrio1

instance FstParam (FrameRate a) a where 
  get1 :: FrameRate a -> a
get1 = FrameRate a -> a
forall a. FrameRate a -> a
frameRate1

instance FstParam (OverSample a) a where 
  get1 :: OverSample a -> a
get1 = OverSample a -> a
forall a. OverSample a -> a
overSample1

instance FstParamM (Bend a b c) a where
  get1m :: Bend a b c -> Maybe a
get1m = Bend a b c -> Maybe a
forall a b c. Bend a b c -> Maybe a
bend1

instance FstParamM (Coeffs a) a where
  get1m :: Coeffs a -> Maybe a
get1m = Int -> Coeffs a -> Maybe a
forall a. Int -> Coeffs a -> Maybe a
coeffs1 Int
1

instance FstParam (Biquad a) (Coeffs a) where
  get1 :: Biquad a -> Coeffs a
get1 = Biquad a -> Coeffs a
forall a. Biquad a -> Coeffs a
biquad1

instance FstParam (Chans a) a where
  get1 :: Chans a -> a
get1 = Chans a -> a
forall a. Chans a -> a
channels1

instance FstParam (ChorusTail a b) a where
  get1 :: ChorusTail a b -> a
get1 = Int -> ChorusTail a b -> a
forall a b. Int -> ChorusTail a b -> a
chorusTail1 Int
1  

instance FstParam (Chorus a b) a where
  get1 :: Chorus a b -> a
get1 = Int -> Chorus a b -> a
forall a b. Int -> Chorus a b -> a
chorus1 Int
1

instance FstParamM (Contrast a) a where
  get1m :: Contrast a -> Maybe a
get1m = Contrast a -> Maybe a
forall a. Contrast a -> Maybe a
contrast1
    
instance FstParam Cntrst Float where
  get1 :: Cntrst -> Float
get1 = Cntrst -> Float
contrastE1

instance FstParam (DCShift a b) a where
  get1 :: DCShift a b -> a
get1 = DCShift a b -> a
forall a b. DCShift a b -> a
dcShift1

instance FstParamL Dlay TSpecification where
  get1L :: Dlay -> [TSpecification]
get1L = Dlay -> [TSpecification]
delay1

instance FstParamM (Filter a) a where
  get1m :: Filter a -> Maybe a
get1m = Filter a -> Maybe a
forall a. Filter a -> Maybe a
filter1

instance FstParamM FilterN NoiseType where
  get1m :: FilterN -> Maybe NoiseType
get1m = FilterN -> Maybe NoiseType
filterN1

instance FstParamM (PrecisionD a) a where 
  get1m :: PrecisionD a -> Maybe a
get1m = PrecisionD a -> Maybe a
forall a. PrecisionD a -> Maybe a
precisionD1

instance FstParamM (Dither a b c) a where 
  get1m :: Dither a b c -> Maybe a
get1m = Dither a b c -> Maybe a
forall a b c. Dither a b c -> Maybe a
dither1

instance FstParamM (Downsample a) a where
  get1m :: Downsample a -> Maybe a
get1m = Downsample a -> Maybe a
forall a. Downsample a -> Maybe a
downSample1

instance FstParam DSample Int where
  get1 :: DSample -> Int
get1 = DSample -> Int
downSampleE1

instance FstParam (EchoTail a) a where
  get1 :: EchoTail a -> a
get1 = Int -> EchoTail a -> a
forall a. Int -> EchoTail a -> a
echoTail1 Int
1  

instance FstParam (Echo a b) a where
  get1 :: Echo a b -> a
get1 = Int -> Echo a b -> a
forall a b. Int -> Echo a b -> a
echo1 Int
1

instance FstParam (Echos a b) a where
  get1 :: Echos a b -> a
get1 = Int -> Echos a b -> a
forall a b. Int -> Echos a b -> a
echos1 Int
1  

instance FstParam (Fade2 a b) a where
  get1 :: Fade2 a b -> a
get1 = Fade2 a b -> a
forall a b. Fade2 a b -> a
fade1

instance FstParam Fade String where
  get1 :: Fade -> String
get1 = Int -> Fade -> String
fade2E Int
1  

instance FstParamM (Fir a b) a where
  get1m :: Fir a b -> Maybe a
get1m = Fir a b -> Maybe a
forall a b. Fir a b -> Maybe a
fir1

instance FstParamL (Flanger a b) a where 
  get1L :: Flanger a b -> [a]
get1L = Flanger a b -> [a]
forall a b. Flanger a b -> [a]
flanger1

instance FstParamL Flanger2 Float where
  get1L :: Flanger2 -> [Float]
get1L = Flanger2 -> [Float]
flanger1E
  
instance FstParam (Gain1 a b c d) a where
  get1 :: Gain1 a b c d -> a
get1 = Gain1 a b c d -> a
forall a b c d. Gain1 a b c d -> a
gain1

instance FstParamM (Hilbert a) a where
  get1m :: Hilbert a -> Maybe a
get1m = Hilbert a -> Maybe a
forall a. Hilbert a -> Maybe a
hilbert1

instance FstParam (Ladspa1 a b c) a where
  get1 :: Ladspa1 a b c -> a
get1 = Ladspa1 a b c -> a
forall a b c. Ladspa1 a b c -> a
ladspa1

instance FstParamM (Loudness a) a where
  get1m :: Loudness a -> Maybe a
get1m = Loudness a -> Maybe a
forall a. Loudness a -> Maybe a
loudness1

instance FstParamM (FloatE a) a where
  get1m :: FloatE a -> Maybe a
get1m = FloatE a -> Maybe a
forall a. FloatE a -> Maybe a
floatE1

instance FstParamM (CompandTail a b) (One2 a) where 
  get1m :: CompandTail a b -> Maybe (One2 a)
get1m = CompandTail a b -> Maybe (One2 a)
forall a b. CompandTail a b -> Maybe (One2 a)
compandTail1

instance FstParam (Pair a) a where 
  get1 :: Pair a -> a
get1 = Pair a -> a
forall a. Pair a -> a
pair1

instance FstParam (AtDe a) a where
  get1 :: AtDe a -> a
get1 = AtDe a -> a
forall a. AtDe a -> a
atDe1

instance FstParam (Neg a) a where
  get1 :: Neg a -> a
get1 = Neg a -> a
forall a. Neg a -> a
neg1

instance FstParamM (SoftKnee a) a where
  get1m :: SoftKnee a -> Maybe a
get1m = SoftKnee a -> Maybe a
forall a. SoftKnee a -> Maybe a
softKnee1

instance FstParam (Compand a b c d) a where
  get1 :: Compand a b c d -> a
get1 = Compand a b c d -> a
forall a b c d. Compand a b c d -> a
compand1
    
instance FstParam KFQ Int where
  get1 :: KFQ -> Int
get1 = KFQ -> Int
kFreq1

instance FstParam (FreqComp a b) a where
  get1 :: FreqComp a b -> a
get1 = FreqComp a b -> a
forall a b. FreqComp a b -> a
freqComp1

instance FstParam (MCompand a b) a where
  get1 :: MCompand a b -> a
get1 = MCompand a b -> a
forall a b. MCompand a b -> a
mCompand1

instance FstParamL (MscS a) a where
  get1L :: MscS a -> [a]
get1L = MscS a -> [a]
forall a. MscS a -> [a]
mscS1

instance FstParamM (Noiseprof a) a where
  get1m :: Noiseprof a -> Maybe a
get1m = Noiseprof a -> Maybe a
forall a. Noiseprof a -> Maybe a
noiseprof1

instance FstParamM (Noisered a b) a where 
  get1m :: Noisered a b -> Maybe a
get1m = Noisered a b -> Maybe a
forall a b. Noisered a b -> Maybe a
noisered1

instance FstParamM (Overdrive a) a where 
  get1m :: Overdrive a -> Maybe a
get1m = Overdrive a -> Maybe a
forall a. Overdrive a -> Maybe a
overdrive1

instance FstParam (PadSpec a) a where
  get1 :: PadSpec a -> a
get1 = PadSpec a -> a
forall a. PadSpec a -> a
padSpec1

instance FstParamL (Pad a b) a where
  get1L :: Pad a b -> [a]
get1L = Pad a b -> [a]
forall a b. Pad a b -> [a]
pad1

instance FstParam (FreqWidth a b) a where
  get1 :: FreqWidth a b -> a
get1 = FreqWidth a b -> a
forall a b. FreqWidth a b -> a
freqWidth1

instance FstParam (Freq a) a where
  get1 :: Freq a -> a
get1 = Freq a -> a
forall a. Freq a -> a
freq1

instance FstParam (AllPass a) a where 
  get1 :: AllPass a -> a
get1 = AllPass a -> a
forall a. AllPass a -> a
allPass1

instance FstParam (BandReject a) a where
  get1 :: BandReject a -> a
get1 = BandReject a -> a
forall a. BandReject a -> a
bandReject1
  
instance FstParam (BandPass a b) a where
  get1 :: BandPass a b -> a
get1 = BandPass a b -> a
forall a b. BandPass a b -> a
bandPass1

instance FstParam (Band a b) a where
  get1 :: Band a b -> a
get1 = Band a b -> a
forall a b. Band a b -> a
band1

instance FstParam (HighPass a b) a where
  get1 :: HighPass a b -> a
get1 = HighPass a b -> a
forall a b. HighPass a b -> a
highPass1

instance FstParam (LowPass a b) a where
  get1 :: LowPass a b -> a
get1 = LowPass a b -> a
forall a b. LowPass a b -> a
lowPass1

instance FstParam (Equalizer a b) a where
  get1 :: Equalizer a b -> a
get1 = Equalizer a b -> a
forall a b. Equalizer a b -> a
equalizer1

instance FstParam (Phaser a b) a where
  get1 :: Phaser a b -> a
get1 = Int -> Phaser a b -> a
forall a b. Int -> Phaser a b -> a
phaser1 Int
1

instance FstParam (Pitch a b c) a where 
  get1 :: Pitch a b c -> a
get1 = Pitch a b c -> a
forall a b c. Pitch a b c -> a
pitch1

instance FstParamM (Ropt4 a) a where 
  get1m :: Ropt4 a -> Maybe a
get1m = Ropt4 a -> Maybe a
forall a. Ropt4 a -> Maybe a
rOpt41

instance FstParamM (Ropt5 a) a where
  get1m :: Ropt5 a -> Maybe a
get1m = Ropt5 a -> Maybe a
forall a. Ropt5 a -> Maybe a
rOpt51

instance FstParam (RateL a b) a where
  get1 :: RateL a b -> a
get1 = RateL a b -> a
forall a b. RateL a b -> a
rateL1

instance FstParam (RateH a b1 b2 b3 b4 b5 c) a where
  get1 :: RateH a b1 b2 b3 b4 b5 c -> a
get1 = RateH a b1 b2 b3 b4 b5 c -> a
forall a b1 b2 b3 b4 b5 c. RateH a b1 b2 b3 b4 b5 c -> a
rateH1

instance FstParamM (Rate2 a b) a where
  get1m :: Rate2 a b -> Maybe a
get1m = Rate2 a b -> Maybe a
forall a b. Rate2 a b -> Maybe a
rate21
    
instance FstParam (Vol3 Float) Float where
  get1 :: Vol3 Float -> Float
get1 = Vol3 Float -> Float
vol31

instance FstParam (IChannel a b) a where
  get1 :: IChannel a b -> a
get1 = IChannel a b -> a
forall a b. IChannel a b -> a
ichannel1

instance FstParam (IChannel a Float) Float where
  get1 :: IChannel a Float -> Float
get1 = IChannel a Float -> Float
forall a. IChannel a Float -> Float
ichannel21

instance FstParamL (OChannel a) a where
  get1L :: OChannel a -> [a]
get1L = OChannel a -> [a]
forall a. OChannel a -> [a]
ochannel1

instance FstParamM (Remix a b) a where
  get1m :: Remix a b -> Maybe a
get1m = Remix a b -> Maybe a
forall a b. Remix a b -> Maybe a
remix1

instance FstParam (Repeat a) a where 
  get1 :: Repeat a -> a
get1 = Repeat a -> a
forall a. Repeat a -> a
repeat1

instance FstParam (Reverb a b c d) a where 
  get1 :: Reverb a b c d -> a
get1 = Reverb a b c d -> a
forall a b c d. Reverb a b c d -> a
reverb1

instance FstParam ReverbE Float where
  get1 :: ReverbE -> Float
get1 = Int -> ReverbE -> Float
reverb3E Int
1  

instance FstParamM (Segment a) a where
  get1m :: Segment a -> Maybe a
get1m = Segment a -> Maybe a
forall a. Segment a -> Maybe a
segment1

instance FstParam (Threshold a) a where
  get1 :: Threshold a -> a
get1 = Threshold a -> a
forall a. Threshold a -> a
threshold1

instance FstParamM (Duration a b) a where
  get1m :: Duration a b -> Maybe a
get1m = Duration a b -> Maybe a
forall a b. Duration a b -> Maybe a
duration1

instance FstParamM (AboveTSpec1 a b c) a where
  get1m :: AboveTSpec1 a b c -> Maybe a
get1m = AboveTSpec1 a b c -> Maybe a
forall a b c. AboveTSpec1 a b c -> Maybe a
aboveTSpec1

instance FstParamM (BelowTSpec1 a b c) a where 
  get1m :: BelowTSpec1 a b c -> Maybe a
get1m = BelowTSpec1 a b c -> Maybe a
forall a b c. BelowTSpec1 a b c -> Maybe a
belowTSpec1

instance FstParam (Silence a b c) a where
  get1 :: Silence a b c -> a
get1 = Silence a b c -> a
forall a b c. Silence a b c -> a
silence1
  
instance FstParamM (PhaseR a) a where
  get1m :: PhaseR a -> Maybe a
get1m = PhaseR a -> Maybe a
forall a. PhaseR a -> Maybe a
phaseR1

instance FstParamM (SincAB a) a where
  get1m :: SincAB a -> Maybe a
get1m = SincAB a -> Maybe a
forall a. SincAB a -> Maybe a
sincAB1

instance FstParamM (SincTN a) a where
  get1m :: SincTN a -> Maybe a
get1m = SincTN a -> Maybe a
forall a. SincTN a -> Maybe a
sincTN1

instance FstParam (FreqL a) a where
  get1 :: FreqL a -> a
get1 = FreqL a -> a
forall a. FreqL a -> a
freqL1

instance FstParam (FreqH a) a where
  get1 :: FreqH a -> a
get1 = FreqH a -> a
forall a. FreqH a -> a
freqH1

instance FstParam (Sinc a b c d) a where 
  get1 :: Sinc a b c d -> a
get1 = Sinc a b c d -> a
forall a b c d. Sinc a b c d -> a
sinc1

instance FstParam Freq1 Float where 
  get1 :: Freq1 -> Float
get1 = Freq1 -> Float
frequency1

instance FstParam (Width a) a where
  get1 :: Width a -> a
get1 = Width a -> a
forall a. Width a -> a
width1

instance FstParam (SFloat1 a) a where
  get1 :: SFloat1 a -> a
get1 = SFloat1 a -> a
forall a. SFloat1 a -> a
sFloat11

instance FstParam (SString1 a) a where
  get1 :: SString1 a -> a
get1 = SString1 a -> a
forall a. SString1 a -> a
sString11

instance FstParam (Advanced1 a) a where
  get1 :: Advanced1 a -> a
get1 = Advanced1 a -> a
forall a. Advanced1 a -> a
advanced11

instance FstParamM FirstDTSpec Float where
  get1m :: FirstDTSpec -> Maybe Float
get1m = FirstDTSpec -> Maybe Float
secondsD
    
instance FstParamM FirstDTSpec Int where
  get1m :: FirstDTSpec -> Maybe Int
get1m = FirstDTSpec -> Maybe Int
samplesD

instance FstParamL (Spectrogram3 a b c d e) a where
  get1L :: Spectrogram3 a b c d e -> [a]
get1L = Spectrogram3 a b c d e -> [a]
forall a b c d e. Spectrogram3 a b c d e -> [a]
spectrogram31

instance FstParam (Speed a b) a where
  get1 :: Speed a b -> a
get1 = Speed a b -> a
forall a b. Speed a b -> a
speed1

instance FstParam (Splice2 a b) a where
  get1 :: Splice2 a b -> a
get1 = Splice2 a b -> a
forall a b. Splice2 a b -> a
splice21

instance FstParamM (StatP a) a where
  get1m :: StatP a -> Maybe a
get1m = StatP a -> Maybe a
forall a. StatP a -> Maybe a
statP1

instance FstParamL (Stat1 a) a where 
  get1L :: Stat1 a -> [a]
get1L = Stat1 a -> [a]
forall a. Stat1 a -> [a]
stat11

instance FstParamM (StatsP a) a where 
  get1m :: StatsP a -> Maybe a
get1m = StatsP a -> Maybe a
forall a. StatsP a -> Maybe a
statsP1

instance FstParamM (Window1 a) a where
  get1m :: Window1 a -> Maybe a
get1m = Window1 a -> Maybe a
forall a. Window1 a -> Maybe a
window11

instance FstParamL (Stats2 a b) a where
  get1L :: Stats2 a b -> [a]
get1L = Stats2 a b -> [a]
forall a b. Stats2 a b -> [a]
stats21

instance FstParam (StretchP a) a where
  get1 :: StretchP a -> a
get1 = StretchP a -> a
forall a. StretchP a -> a
stretch1

instance FstParam (Stretch2 a b) a where
  get1 :: Stretch2 a b -> a
get1 = Stretch2 a b -> a
forall a b. Stretch2 a b -> a
stretch21

instance FstParam (Tempo a b c d) a where 
  get1 :: Tempo a b c d -> a
get1 = Tempo a b c d -> a
forall a b c d. Tempo a b c d -> a
tempo1

instance FstParamM FirstTSpec Float where
  get1m :: FirstTSpec -> Maybe Float
get1m = FirstTSpec -> Maybe Float
seconds
  
instance FstParamM FirstTSpec Int where
  get1m :: FirstTSpec -> Maybe Int
get1m = FirstTSpec -> Maybe Int
samples

instance FstParamM NextTSpec Float where
  get1m :: NextTSpec -> Maybe Float
get1m = NextTSpec -> Maybe Float
seconds2
  
instance FstParamM NextTSpec Int where
  get1m :: NextTSpec -> Maybe Int
get1m = NextTSpec -> Maybe Int
samples2

instance FstParam (TimeSpec a b) a where
  get1 :: TimeSpec a b -> a
get1 = TimeSpec a b -> a
forall a b. TimeSpec a b -> a
timeSpec1

instance FstParam (Tremolo a) a where
  get1 :: Tremolo a -> a
get1 = Tremolo a -> a
forall a. Tremolo a -> a
tremolo1

instance FstParam (Trim a) a where 
  get1 :: Trim a -> a
get1 = Trim a -> a
forall a. Trim a -> a
trim1

instance FstParamM (Upsample a) a where 
  get1m :: Upsample a -> Maybe a
get1m = Upsample a -> Maybe a
forall a. Upsample a -> Maybe a
upSample1

instance FstParam (VadP a) a where
  get1 :: VadP a -> a
get1 = VadP a -> a
forall a. VadP a -> a
vadP1

instance FstParamL (Vad1 a) a where
  get1L :: Vad1 a -> [a]
get1L = Vad1 a -> [a]
forall a. Vad1 a -> [a]
vad11

instance FstParam (Vol2 a b) a where
  get1 :: Vol2 a b -> a
get1 = Vol2 a b -> a
forall a b. Vol2 a b -> a
vol1

instance FstParamL (One2 a) a where
  get1L :: One2 a -> [a]
get1L = One2 a -> [a]
forall a. One2 a -> [a]
one21

instance FstParamL (One3 a) a where
  get1L :: One3 a -> [a]
get1L = One3 a -> [a]
forall a. One3 a -> [a]
one31

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