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

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

module DobutokO.Sound.Effects.Tremolo where

#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__>=710
/* code that applies only to GHC 7.10.* and higher versions */
import GHC.Base (mconcat)
#endif
#endif

import Numeric (showFFloat)
import DobutokO.Sound.ToRange

#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif

data Tremolo a = TL1 a | TL2 a a deriving Tremolo a -> Tremolo a -> Bool
(Tremolo a -> Tremolo a -> Bool)
-> (Tremolo a -> Tremolo a -> Bool) -> Eq (Tremolo a)
forall a. Eq a => Tremolo a -> Tremolo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tremolo a -> Tremolo a -> Bool
$c/= :: forall a. Eq a => Tremolo a -> Tremolo a -> Bool
== :: Tremolo a -> Tremolo a -> Bool
$c== :: forall a. Eq a => Tremolo a -> Tremolo a -> Bool
Eq

instance Show (Tremolo Float) where
  show :: Tremolo Float -> String
show (TL1 Float
x) = [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"tremolo ", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat Maybe Int
forall a. Maybe a
Nothing (Float -> Float
forall a. Num a => a -> a
abs Float
x) String
" "]
  show (TL2 Float
x Float
y) = [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"tremolo ", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat Maybe Int
forall a. Maybe a
Nothing (Float -> Float
forall a. Num a => a -> a
abs Float
x) String
" ", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat Maybe Int
forall a. Maybe a
Nothing (Float -> Float -> Float
toRange Float
100.0 (Float -> Float
forall a. Num a => a -> a
abs Float
y)) String
" "]
  
type Treml = Tremolo Float

tremoloC :: Tremolo a -> String
tremoloC :: Tremolo a -> String
tremoloC (TL1 a
_) = String
"TL1"
tremoloC Tremolo a
_ = String
"TL2"

tremolo1 :: Tremolo a -> a
tremolo1 :: Tremolo a -> a
tremolo1 (TL1 a
x) = a
x
tremolo1 (TL2 a
x a
_) = a
x

tremolo2 :: Tremolo a -> Maybe a
tremolo2 :: Tremolo a -> Maybe a
tremolo2 (TL2 a
_ a
y) = a -> Maybe a
forall a. a -> Maybe a
Just a
y
tremolo2 Tremolo a
_ = Maybe a
forall a. Maybe a
Nothing

tremoloSet1 :: a -> Tremolo a -> Tremolo a
tremoloSet1 :: a -> Tremolo a -> Tremolo a
tremoloSet1 a
x (TL2 a
_ a
y) = a -> a -> Tremolo a
forall a. a -> a -> Tremolo a
TL2 a
x a
y
tremoloSet1 a
x Tremolo a
_ = a -> Tremolo a
forall a. a -> Tremolo a
TL1 a
x

tremoloSet2 :: a -> Tremolo a -> Tremolo a
tremoloSet2 :: a -> Tremolo a -> Tremolo a
tremoloSet2 a
y (TL2 a
x a
_) = a -> a -> Tremolo a
forall a. a -> a -> Tremolo a
TL2 a
x a
y
tremoloSet2 a
y (TL1 a
x) = a -> a -> Tremolo a
forall a. a -> a -> Tremolo a
TL2 a
x a
y

showTLQ :: Treml -> [String]
showTLQ :: Tremolo Float -> [String]
showTLQ = String -> [String]
words (String -> [String])
-> (Tremolo Float -> String) -> Tremolo Float -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tremolo Float -> String
forall a. Show a => a -> String
show