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

import DobutokO.Sound.Effects.Bend
import DobutokO.Sound.Effects.Biquad
import DobutokO.Sound.Effects.Chorus
import DobutokO.Sound.Effects.Dither
import DobutokO.Sound.Effects.Echo
import DobutokO.Sound.Effects.Fade
import DobutokO.Sound.Effects.Gain
import DobutokO.Sound.Effects.LADSPA
import DobutokO.Sound.Effects.MCompand
import DobutokO.Sound.Effects.Phaser
import DobutokO.Sound.Effects.Pitch
import DobutokO.Sound.Effects.Rate
import DobutokO.Sound.Effects.Reverb
import DobutokO.Sound.Effects.Segment
import DobutokO.Sound.Effects.Silence
import DobutokO.Sound.Effects.Sinc
import DobutokO.Sound.Effects.Spectrogram
import DobutokO.Sound.Effects.Stretch
import DobutokO.Sound.Effects.Tempo
import DobutokO.Sound.Effects.Timespec
import DobutokO.Sound.Effects.Vol
import DobutokO.Sound.One

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 :: BendTrio a b -> a
get3 = BendTrio a b -> a
forall a b. BendTrio a b -> a
bendTrio3

instance ThdParam (Bend a b c) c where
  get3 :: Bend a b c -> c
get3 = Bend a b c -> c
forall a b c. Bend a b c -> c
bend3

instance ThdParamM (Coeffs a) a where
  get3m :: Coeffs a -> Maybe a
get3m = Int -> Coeffs a -> Maybe a
forall a. Int -> Coeffs a -> Maybe a
coeffs1 Int
3

instance ThdParam (ChorusTail a b) a where
  get3 :: ChorusTail a b -> a
get3 = Int -> ChorusTail a b -> a
forall a b. Int -> ChorusTail a b -> a
chorusTail1 Int
3

instance ThdParamL (Chorus a b) b where
  get3L :: Chorus a b -> [b]
get3L = Chorus a b -> [b]
forall a b. Chorus a b -> [b]
chorus2

instance ThdParamM (Dither a b c) c where 
  get3m :: Dither a b c -> Maybe c
get3m = Dither a b c -> Maybe c
forall a b c. Dither a b c -> Maybe c
dither3

instance ThdParamL (Echo a b) b where
  get3L :: Echo a b -> [b]
get3L = Echo a b -> [b]
forall a b. Echo a b -> [b]
echo2

instance ThdParamL (Echos a b) b where
  get3L :: Echos a b -> [b]
get3L = Echos a b -> [b]
forall a b. Echos a b -> [b]
echos2  

instance ThdParam Fade String where
  get3 :: Fade -> String
get3 = Int -> Fade -> String
fade2E Int
3

instance ThdParam (Gain1 a b c d) c where
  get3 :: Gain1 a b c d -> c
get3 = Gain1 a b c d -> c
forall a b c d. Gain1 a b c d -> c
gain3

instance ThdParamM (Ladspa1 a b c) c where
  get3m :: Ladspa1 a b c -> Maybe c
get3m = Ladspa1 a b c -> Maybe c
forall a b c. Ladspa1 a b c -> Maybe c
ladspa3

instance ThdParam (Compand a b c d) c where
  get3 :: Compand a b c d -> c
get3 = Compand a b c d -> c
forall a b c d. Compand a b c d -> c
compand3

instance ThdParam (Phaser a b) a where
  get3 :: Phaser a b -> a
get3 = Int -> Phaser a b -> a
forall a b. Int -> Phaser a b -> a
phaser1 Int
3

instance ThdParamM (Pitch a b c) c where 
  get3m :: Pitch a b c -> Maybe c
get3m = Pitch a b c -> Maybe c
forall a b c. Pitch a b c -> Maybe c
pitch3

instance ThdParam (RateH a b1 b2 b3 b4 b5 c) b2 where
  get3 :: RateH a b1 b2 b3 b4 b5 c -> b2
get3 = RateH a b1 b2 b3 b4 b5 c -> b2
forall a b1 b2 b3 b4 b5 c. RateH a b1 b2 b3 b4 b5 c -> b2
rateH22

instance ThdParamL (Reverb a b c d) c where 
  get3L :: Reverb a b c d -> [c]
get3L = Reverb a b c d -> [c]
forall a b c d. Reverb a b c d -> [c]
reverb3

instance ThdParam ReverbE Float where
  get3 :: ReverbE -> Float
get3 = Int -> ReverbE -> Float
reverb3E Int
3

instance ThdParamM (Segment a) a where
  get3m :: Segment a -> Maybe a
get3m = Segment a -> Maybe a
forall a. Segment a -> Maybe a
segment3

instance ThdParamM (AboveTSpec1 a b c) c where
  get3m :: AboveTSpec1 a b c -> Maybe c
get3m = AboveTSpec1 a b c -> Maybe c
forall a b c. AboveTSpec1 a b c -> Maybe c
aboveTSpec3

instance ThdParamM (BelowTSpec1 a b c) c where 
  get3m :: BelowTSpec1 a b c -> Maybe c
get3m = BelowTSpec1 a b c -> Maybe c
forall a b c. BelowTSpec1 a b c -> Maybe c
belowTSpec3

instance ThdParamM (Silence a b c) c where
  get3m :: Silence a b c -> Maybe c
get3m = Silence a b c -> Maybe c
forall a b c. Silence a b c -> Maybe c
silence3
  
instance ThdParam (Sinc a b c d) (One2 c) where 
  get3 :: Sinc a b c d -> One2 c
get3 = Sinc a b c d -> One2 c
forall a b c d. Sinc a b c d -> One2 c
sinc3

instance ThdParamM FirstDTSpec Int where
  get3m :: FirstDTSpec -> Maybe Int
get3m = FirstDTSpec -> Maybe Int
hoursD
    
instance ThdParamL (Spectrogram3 a b c d e) c where
  get3L :: Spectrogram3 a b c d e -> [c]
get3L = Spectrogram3 a b c d e -> [c]
forall a b c d e. Spectrogram3 a b c d e -> [c]
spectrogram33

instance ThdParam (StretchP a) a where
  get3 :: StretchP a -> a
get3 = StretchP a -> a
forall a. StretchP a -> a
stretch3

instance ThdParam (Tempo a b c d) c where 
  get3 :: Tempo a b c d -> c
get3 = Tempo a b c d -> c
forall a b c d. Tempo a b c d -> c
tempo3

instance ThdParamM FirstTSpec Int where
  get3m :: FirstTSpec -> Maybe Int
get3m = FirstTSpec -> Maybe Int
hours
  
instance ThdParamM NextTSpec Int where
  get3m :: NextTSpec -> Maybe Int
get3m = NextTSpec -> Maybe Int
hours2

instance ThdParamM (Vol2 a b) a where
  get3m :: Vol2 a b -> Maybe a
get3m = Vol2 a b -> Maybe a
forall a b. Vol2 a b -> Maybe a
vol3