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

import Numeric (showFFloat)
import DobutokO.Sound.ToRange
import DobutokO.Sound.Effects.Misc (MscS(..),mscS1)
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.Modulation2
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 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 = freqWidthS1

instance FstParam (Bass a b) a where
  get1 = bass1

instance FstParam (Treble a b) a where
  get1 = treble1

instance FstParam (BendTrio a b) a where
  get1 = bendTrio1

instance FstParam (FrameRate a) a where
  get1 = frameRate1

instance FstParam (OverSample a) a where
  get1 = overSample1

instance FstParamM (Bend a b c) a where
  get1m = bend1

instance FstParamM (Coeffs a) a where
  get1m = coeffs1 1

instance FstParam (Biquad a) (Coeffs a) where
  get1 = biquad1

instance FstParam (Chans a) a where
  get1 = channels1

instance FstParam (ChorusTail a b) a where
  get1 = chorusTail1 1

instance FstParam (Chorus a b) a where
  get1 = chorus1 1

instance FstParamM (Contrast a) a where
  get1m = contrast1

instance FstParam Cntrst Float where
  get1 = contrastE1

instance FstParam (DCShift a b) a where
  get1 = dcShift1

instance FstParamL Dlay TSpecification where
  get1L = delay1

instance FstParamM (Filter a) a where
  get1m = filter1

instance FstParamM FilterN NoiseType where
  get1m = filterN1

instance FstParamM (PrecisionD a) a where
  get1m = precisionD1

instance FstParamM (Dither a b c) a where
  get1m = dither1

instance FstParamM (Downsample a) a where
  get1m = downSample1

instance FstParam DSample Int where
  get1 = downSampleE1

instance FstParam (EchoTail a) a where
  get1 = echoTail1 1

instance FstParam (Echo a b) a where
  get1 = echo1 1

instance FstParam (Echos a b) a where
  get1 = echos1 1

instance FstParam (Fade2 a b) a where
  get1 = fade1

instance FstParam Fade String where
  get1 = fade2E 1

instance FstParamM (Fir a b) a where
  get1m = fir1

instance FstParamL (Flanger a b) a where
  get1L = flanger1

instance FstParamL Flanger2 Float where
  get1L = flanger1E

instance FstParam (Gain1 a b c d) a where
  get1 = gain1

instance FstParamM (Hilbert a) a where
  get1m = hilbert1

instance FstParam (Ladspa1 a b c) a where
  get1 = ladspa1

instance FstParamM (Loudness a) a where
  get1m = loudness1

instance FstParamM (FloatE a) a where
  get1m = floatE1

instance FstParamM (CompandTail a b) (One2 a) where
  get1m = compandTail1

instance FstParam (Pair a) a where
  get1 = pair1

instance FstParam (AtDe a) a where
  get1 = atDe1

instance FstParam (Neg a) a where
  get1 = neg1

instance FstParamM (SoftKnee a) a where
  get1m = softKnee1

instance FstParam (Compand a b c d) a where
  get1 = compand1

instance FstParam KFQ Int where
  get1 = kFreq1

instance FstParam (FreqComp a b) a where
  get1 = freqComp1

instance FstParam (MCompand a b) a where
  get1 = mCompand1

instance FstParamL (MscS a) a where
  get1L = mscS1

instance FstParamM (Noiseprof a) a where
  get1m = noiseprof1

instance FstParamM (Noisered a b) a where
  get1m = noisered1

instance FstParamM (Overdrive a) a where
  get1m = overdrive1

instance FstParam (PadSpec a) a where
  get1 = padSpec1

instance FstParamL (Pad a b) a where
  get1L = pad1

instance FstParam (FreqWidth a b) a where
  get1 = freqWidth1

instance FstParam (Freq a) a where
  get1 = freq1

instance FstParam (AllPass a) a where
  get1 = allPass1

instance FstParam (BandReject a) a where
  get1 = bandReject1

instance FstParam (BandPass a b) a where
  get1 = bandPass1

instance FstParam (Band a b) a where
  get1 = band1

instance FstParam (HighPass a b) a where
  get1 = highPass1

instance FstParam (LowPass a b) a where
  get1 = lowPass1

instance FstParam (Equalizer a b) a where
  get1 = equalizer1

instance FstParam (Phaser a b) a where
  get1 = phaser1 1

instance FstParam (Pitch a b c) a where
  get1 = pitch1

instance FstParamM (Ropt4 a) a where
  get1m = rOpt41

instance FstParamM (Ropt5 a) a where
  get1m = rOpt51

instance FstParam (RateL a b) a where
  get1 = rateL1

instance FstParam (RateH a b1 b2 b3 b4 b5 c) a where
  get1 = rateH1

instance FstParamM (Rate2 a b) a where
  get1m = rate21

instance FstParam (Vol3 Float) Float where
  get1 = vol31

instance FstParam (IChannel a b) a where
  get1 = ichannel1

instance FstParam (IChannel a Float) Float where
  get1 = ichannel21

instance FstParamL (OChannel a) a where
  get1L = ochannel1

instance FstParamM (Remix a b) a where
  get1m = remix1

instance FstParam (Repeat a) a where
  get1 = repeat1

instance FstParam (Reverb a b c d) a where
  get1 = reverb1

instance FstParam ReverbE Float where
  get1 = reverb3E 1

instance FstParamM (Segment a) a where
  get1m = segment1

instance FstParam (Threshold a) a where
  get1 = threshold1

instance FstParamM (Duration a b) a where
  get1m = duration1

instance FstParamM (AboveTSpec1 a b c) a where
  get1m = aboveTSpec1

instance FstParamM (BelowTSpec1 a b c) a where
  get1m = belowTSpec1

instance FstParam (Silence a b c) a where
  get1 = silence1

instance FstParamM (PhaseR a) a where
  get1m = phaseR1

instance FstParamM (SincAB a) a where
  get1m = sincAB1

instance FstParamM (SincTN a) a where
  get1m = sincTN1

instance FstParam (FreqL a) a where
  get1 = freqL1

instance FstParam (FreqH a) a where
  get1 = freqH1

instance FstParam (Sinc a b c d) a where
  get1 = sinc1

instance FstParam Freq1 Float where
  get1 = frequency1

instance FstParam (SFloat1 a) a where
  get1 = sFloat11

instance FstParam (SString1 a) a where
  get1 = sString11

instance FstParam (Advanced1 a) a where
  get1 = advanced11

instance FstParamM FirstDTSpec Float where
  get1m = secondsD

instance FstParamM FirstDTSpec Int where
  get1m = samplesD

instance FstParamL (Spectrogram3 a b c d e) a where
  get1L = spectrogram31

instance FstParam (Speed a b) a where
  get1 = speed1

instance FstParam (Splice2 a b) a where
  get1 = splice21

instance FstParamM (StatP a) a where
  get1m = statP1

instance FstParamL (Stat1 a) a where
  get1L = stat11

instance FstParamM (StatsP a) a where
  get1m = statsP1

instance FstParamM (Window1 a) a where
  get1m = window11

instance FstParamL (Stats2 a b) a where
  get1L = stats21

instance FstParam (StretchP a) a where
  get1 = stretch1

instance FstParam (Stretch2 a b) a where
  get1 = stretch21

instance FstParam (Tempo a b c d) a where
  get1 = tempo1

instance FstParamM FirstTSpec Float where
  get1m = seconds

instance FstParamM FirstTSpec Int where
  get1m = samples

instance FstParamM NextTSpec Float where
  get1m = seconds2

instance FstParamM NextTSpec Int where
  get1m = samples2

instance FstParam (TimeSpec a b) a where
  get1 = timeSpec1

instance FstParam (Tremolo a) a where
  get1 = tremolo1

instance FstParam (Trim a) a where
  get1 = trim1

instance FstParamM (Upsample a) a where
  get1m = upSample1

instance FstParam (VadP a) a where
  get1 = vadP1

instance FstParamL (Vad1 a) a where
  get1L = vad11

instance FstParam (Vol2 a b) a where
  get1 = vol1

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

class SndParam a b where
  get2 :: a -> b

class SndParamL a b where
  get2L :: a -> [b]

class SndParamM a b where
  get2m :: a -> Maybe b

instance SndParamM (FreqWidthS a b) b where
  get2m = freqWidthS2

instance SndParam (Bass a b) b where
  get2 = bass2

instance SndParam (Treble a b) b where
  get2 = treble2

instance SndParam (BendTrio a b) b where
  get2 = bendTrio2

instance SndParamM (Bend a b c) b where
  get2m = bend2

instance SndParamM (Coeffs a) a where
  get2m = coeffs1 2

instance SndParam (Biquad a) (Coeffs a) where
  get2 = biquad2

instance SndParam (ChorusTail a b) a where
  get2 = chorusTail1 2

instance SndParam (Chorus a b) a where
  get2 = chorus1 2

instance SndParamM (DCShift a b) b where
  get2m = dcShift2

instance SndParamM (Dither a b c) b where
  get2m = dither2

instance SndParam (EchoTail a) a where
  get2 = echoTail1 2

instance SndParam (Echo a b) a where
  get2 = echo1 2

instance SndParam (Echos a b) a where
  get2 = echos1 2

instance SndParamL (Fade2 a b) b where
  get2L = fade2

instance SndParam Fade String where
  get2 = fade2E 2

instance SndParamM (Fir a b) [b] where
  get2m = fir2

instance SndParam (Flanger a b) b where
  get2 = flanger2

instance SndParam (Gain1 a b c d) b where
  get2 = gain2

instance SndParam (Ladspa1 a b c) (One2 b) where
  get2 = ladspa2

instance SndParamM (Loudness a) a where
  get2m = loudness2

instance SndParamM (CompandTail a b) b where
  get2m = compandTail2

instance SndParam (Pair a) a where
  get2 = pair2

instance SndParamL (AtDe a) a where
  get2L = atDe2

instance SndParam (Compand a b c d) b where
  get2 = compand2

instance SndParam (FreqComp a b) b where
  get2 = freqComp2

instance SndParamM (MCompand a b) [b] where
  get2m = mCompand2

instance SndParamM (Noisered a b) b where
  get2m = noisered2

instance SndParamM (Overdrive a) a where
  get2m = overdrive2

instance SndParam (PadSpec a) a where
  get2 = padSpec2

instance SndParamL (Pad a b) b where
  get2L = pad2

instance SndParamM (FreqWidth a b) b where
  get2m = freqWidth2

instance SndParam (BandPass a b) b where
  get2 = bandPass2

instance SndParam (Band a b) b where
  get2 = band2

instance SndParam (HighPass a b) b where
  get2 = highPass2

instance SndParam (LowPass a b) b where
  get2 = lowPass2

instance SndParam (Equalizer a b) b where
  get2 = equalizer2

instance SndParam (Phaser a b) a where
  get2 = phaser1 2

instance SndParam (Pitch a b c) b where
  get2 = pitch2

instance SndParam (RateL a b) b where
  get2 = rateL2

instance SndParam (RateH a b1 b2 b3 b4 b5 c) b1 where
  get2 = rateH21

instance SndParamM (Rate2 a b) b where
  get2m = rate22

instance SndParamL (Remix a b) b where
  get2L = remix2

instance SndParam (Reverb a b c d) b where
  get2 = reverb2

instance SndParam ReverbE Float where
  get2 = reverb3E 2

instance SndParamM (Segment a) a where
  get2m = segment2

instance SndParamM (Duration a b) b where
  get2m = duration2

instance SndParamM (AboveTSpec1 a b c) b where
  get2m = aboveTSpec2

instance SndParamM (BelowTSpec1 a b c) b where
  get2m = belowTSpec2

instance SndParam (Silence a b c) b where
  get2 = silence2

instance SndParam (Sinc a b c d) b where
  get2 = sinc2

instance SndParamM FirstDTSpec Int where
  get2m = minutesD

instance SndParamL (Spectrogram3 a b c d e) b where
  get2L = spectrogram32

instance SndParam (Speed a b) b where
  get2 = speed2

instance SndParamL (Splice2 a b) (One3 b) where
  get2L = splice22

instance SndParamL (Stats2 a b) b where
  get2L = stats22

instance SndParam (StretchP a) a where
  get2 = stretch2

instance SndParamM (Stretch2 a b) b where
  get2m = stretch22

instance SndParam (Tempo a b c d) b where
  get2 = tempo2

instance SndParamM FirstTSpec Int where
  get2m = minutes

instance SndParamM NextTSpec Int where
  get2m = minutes2

instance SndParamM (TimeSpec a b) [b] where
  get2m = timeSpec2

instance SndParamM (Tremolo a) a where
  get2m = tremolo2

instance SndParamM (Vol2 a b) b where
  get2m = vol2

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

class ThdParam a b where
  get3 :: a -> b

class ThdParamL a b where
  get3L :: a -> [b]

class ThdParamM a b where
  get3m :: a -> Maybe b

instance ThdParam (BendTrio a b) a where
  get3 = bendTrio3

instance ThdParam (Bend a b c) c where
  get3 = bend3

instance ThdParamM (Coeffs a) a where
  get3m = coeffs1 3

instance ThdParam (ChorusTail a b) a where
  get3 = chorusTail1 3

instance ThdParamL (Chorus a b) b where
  get3L = chorus2

instance ThdParamM (Dither a b c) c where
  get3m = dither3

instance ThdParamL (Echo a b) b where
  get3L = echo2

instance ThdParamL (Echos a b) b where
  get3L = echos2

instance ThdParam Fade String where
  get3 = fade2E 3

instance ThdParam (Gain1 a b c d) c where
  get3 = gain3

instance ThdParamM (Ladspa1 a b c) c where
  get3m = ladspa3

instance ThdParam (Compand a b c d) c where
  get3 = compand3

instance ThdParam (Phaser a b) a where
  get3 = phaser1 3

instance ThdParamM (Pitch a b c) c where
  get3m = pitch3

instance ThdParam (RateH a b1 b2 b3 b4 b5 c) b2 where
  get3 = rateH22

instance ThdParamL (Reverb a b c d) c where
  get3L = reverb3

instance ThdParam ReverbE Float where
  get3 = reverb3E 3

instance ThdParamM (Segment a) a where
  get3m = segment3

instance ThdParamM (AboveTSpec1 a b c) c where
  get3m = aboveTSpec3

instance ThdParamM (BelowTSpec1 a b c) c where
  get3m = belowTSpec3

instance ThdParamM (Silence a b c) c where
  get3m = silence3

instance ThdParam (Sinc a b c d) (One2 c) where
  get3 = sinc3

instance ThdParamM FirstDTSpec Int where
  get3m = hoursD

instance ThdParamL (Spectrogram3 a b c d e) c where
  get3L = spectrogram33

instance ThdParam (StretchP a) a where
  get3 = stretch3

instance ThdParam (Tempo a b c d) c where
  get3 = tempo3

instance ThdParamM FirstTSpec Int where
  get3m = hours

instance ThdParamM NextTSpec Int where
  get3m = hours2

instance ThdParamM (Vol2 a b) a where
  get3m = vol3

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

class FourthParam a b where
  get4 :: a -> b

class FourthParamL a b where
  get4L :: a -> [b]

class FourthParamM a b where
  get4m :: a -> Maybe b

instance FourthParam (ChorusTail a b) a where
  get4 = chorusTail1 4

instance FourthParam (Gain1 a b c d) d where
  get4 = gain4

instance FourthParamM (Compand a b c d) d where
  get4m = compand4

instance FourthParam (Phaser a b) a where
  get4 = phaser1 4

instance FourthParam (RateH a b1 b2 b3 b4 b5 c) b3 where
  get4 = rateH23

instance FourthParam (Reverb a b c d) d where
  get4 = reverb4

instance FourthParam ReverbE Float where
  get4 = reverb3E 4

instance FourthParam (Sinc a b c d) d where
  get4 = sinc4

instance FourthParamL (Spectrogram3 a b c d e) d where
  get4L = spectrogram34

instance FourthParamM (Tempo a b c d) d where
  get4m = tempo4

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

class FifthParam a b where
  get5 :: a -> b

class FifthParamL a b where
  get5L :: a -> [b]

class FifthParamM a b where
  get5m :: a -> Maybe b

instance FifthParam (Phaser a b) a where
  get5 = phaser1 5

instance FifthParam (RateH a b1 b2 b3 b4 b5 c) b4 where
  get5 = rateH24

instance FifthParam ReverbE Float where
  get5 = reverb3E 5

instance FifthParamL (Spectrogram3 a b c d e) e where
  get5L = spectrogram35

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

class SixthParam a b where
  get6 :: a -> b

class SixthParamL a b where
  get6L :: a -> [b]

class SixthParamM a b where
  get6m :: a -> Maybe b

instance SixthParam (Phaser a b) b where
  get6 = phaser2

instance SixthParam (RateH a b1 b2 b3 b4 b5 c) b5 where
  get6 = rateH25

instance SixthParam ReverbE Float where
  get6 = reverb3E 6

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

class SeventhParam a b where
  get7 :: a -> b

class SeventhParamL a b where
  get7L :: a -> [b]

class SeventhParamM a b where
  get7m :: a -> Maybe b

instance SeventhParam (RateH a b1 b2 b3 b4 b5 c) c where
  get7 = rateH3

-- ========================================================================================