-- |
-- Module      :  DobutokO.Sound.Functional
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library to create experimental music
-- from a mono audio and a Ukrainian text.

{-# OPTIONS_GHC -threaded #-}

module DobutokO.Sound.Functional (
  -- * Use additional function as a parameter
  oberSoXSynth2FDN
  , oberSoXSynth2FDN_B
  , oberSoXSynth2FDN_B2
) where

import Numeric
import Data.List (isPrefixOf,sort,sortBy,nubBy)
import Data.Maybe (isNothing,fromJust)
import qualified Data.Vector as V
import System.Process
import EndOfExe
import System.Directory
import Melodics.Ukrainian
import DobutokO.Sound hiding (oberSoXSynth2FDN)

-- | Similar to 'oberSoXSynth2DN' but instead of 'oberTones' function, it uses volatile function @f::Double -> Vector (Double, Double)@ with
-- somewhat sophisticated mechanism to normalize the resulting 'V.Vector' elements @(Double, Double)@. The last one is experimental feature, so
-- it is your responsibility to provide a function so that it does not lead to clipping. In such a case, the result of application of the
-- 'convertToProperUkrainian' to the 'String' parameter must not be 'V.empty'.
--
-- Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function.
-- But for a lot of functions this works well.
oberSoXSynth2FDN :: (Double -> V.Vector (Double, Double)) -> Double -> Double -> String -> IO ()
oberSoXSynth2FDN f x y zs
 | V.null . convertToProperUkrainian $ zs = oberSoXSynth x
 | otherwise = do
    let note0 = closestNote (if x /= 0.0 then abs x else V.unsafeIndex notes 0)
        note1 = dNote (V.unsafeIndex (intervalsFromString zs) 0) note0
        g0    = V.fromList . nubBy (\(x1,_) (x2,_) -> x1 == x2) . sortBy (\(x1,_) (x2,_) -> compare x1 x2) . V.toList . V.map (\(noteX, amplX) ->
           if noteX <= 0.0 then (fromIntegral 2 * note0, abs (amplX - (fromIntegral . truncate $ amplX))) else (closestNote noteX,
             abs (amplX - (fromIntegral . truncate $ amplX)))) . f
        g k   = V.takeWhile (\w -> compare (fst w) (V.unsafeIndex notes 107) /= GT && compare (snd w) 0.001 == GT) .
                   V.imap (\i (noteY,z0) -> (fromIntegral (i + 1) * (fst . V.unsafeIndex (g0 k) $ 0), z0)) . g0 $ k
        v0    = g note0
        v1    = if isNothing note1 then V.empty
                else g . fromJust $ note1
        oberSoXSynthHelp vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
        oberSoXSynthHelp2 vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
    _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
       showFFloat (Just 4) note0 $ show 0] ""
    if isNothing note1 then do
      oberSoXSynthHelp v0
    else do
      _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
         showFFloat (Just 4) (fromJust note1) $ show 0] ""
      oberSoXSynthHelp v0
      oberSoXSynthHelp2 v1
    paths0 <- listDirectory "."
    let paths = sort . filter (isPrefixOf "test") $ paths0
    _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result.wav","vol","0.3"]) ""
    mapM_ removeFile paths

-- | Similar to 'oberSoXSynth2FDN' but you specify additional third 'Double' argument from range [0.1..10.0] that is a difference between neighbour frequencies
-- in Hz that is used to filter the frequencies that can cause beating because of close frequencies. If it is not in the range, then the function tries to
-- reposition its value to the range. 
--
-- Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function.
-- But for a lot of functions this works well.
oberSoXSynth2FDN_B :: (Double -> V.Vector (Double, Double)) -> Double -> Double -> Double -> String -> IO ()
oberSoXSynth2FDN_B f x y limB zs
 | V.null . convertToProperUkrainian $ zs = oberSoXSynth x
 | otherwise = do
    let limA0 = abs ((limB / fromIntegral 10) - (fromIntegral . truncate $ (limB / fromIntegral 10))) * fromIntegral 10
        limA  = if compare limA 0.1 == LT then 0.1 else limA
        note0 = closestNote (if x /= 0.0 then abs x else V.unsafeIndex notes 0)
        note1 = dNote (V.unsafeIndex (intervalsFromString zs) 0) note0
        g0    = V.fromList . nubBy (\(x1,_) (x2,_) -> x1 == x2) . sortBy (\(x1,_) (x2,_) -> compare x1 x2) . V.toList . V.map (\(noteX, amplX) ->
           if noteX <= 0.0 then (fromIntegral 2 * note0, abs (amplX - (fromIntegral . truncate $ amplX))) else (closestNote noteX,
             abs (amplX - (fromIntegral . truncate $ amplX)))) . f
        g k   = V.takeWhile (\w -> compare (fst w) (V.unsafeIndex notes 107) /= GT && compare (snd w) 0.001 == GT) . V.fromList .
                   nubBy (\(x1,_) (x2,_) -> compare (abs (x1 - x2)) limA /= GT) . V.toList . V.imap (\i (noteY,z0) -> (fromIntegral (i + 1) * (fst . V.unsafeIndex (g0 k) $
                      0), z0)) . g0 $ k
        v0    = g note0
        v1    = if isNothing note1 then V.empty
                else g . fromJust $ note1
        oberSoXSynthHelp vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
        oberSoXSynthHelp2 vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
    _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
       showFFloat (Just 4) note0 $ show 0] ""
    if isNothing note1 then do
      oberSoXSynthHelp v0
    else do
      _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
         showFFloat (Just 4) (fromJust note1) $ show 0] ""
      oberSoXSynthHelp v0
      oberSoXSynthHelp2 v1
    paths0 <- listDirectory "."
    let paths = sort . filter (isPrefixOf "test") $ paths0
    _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result.wav","vol","0.3"]) ""
    mapM_ removeFile paths

-- | Similar to 'oberSoXSynth2FDN_B' but the function does not try to make real obertones, so the class of functions that it can use may be broader. 
--
-- Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function.
-- But for a lot of functions this works well.
oberSoXSynth2FDN_B2 :: (Double -> V.Vector (Double, Double)) -> Double -> Double -> Double -> String -> IO ()
oberSoXSynth2FDN_B2 f x y limB zs
 | V.null . convertToProperUkrainian $ zs = oberSoXSynth x
 | otherwise = do
    let limA0 = abs ((limB / fromIntegral 10) - (fromIntegral . truncate $ (limB / fromIntegral 10))) * fromIntegral 10
        limA  = if compare limA 0.1 == LT then 0.1 else limA
        note0 = closestNote (if x /= 0.0 then abs x else V.unsafeIndex notes 0)
        note1 = dNote (V.unsafeIndex (intervalsFromString zs) 0) note0
        g0    = V.fromList . nubBy (\(x1,_) (x2,_) -> x1 == x2) . sortBy (\(x1,_) (x2,_) -> compare x1 x2) . V.toList . V.map (\(noteX, amplX) ->
           if noteX <= 0.0 then (fromIntegral 2 * note0, abs (amplX - (fromIntegral . truncate $ amplX))) else (closestNote noteX,
             abs (amplX - (fromIntegral . truncate $ amplX)))) . f
        g k   = V.takeWhile (\w -> compare (fst w) (V.unsafeIndex notes 107) /= GT && compare (snd w) 0.001 == GT) . V.fromList .
                   nubBy (\(x1,_) (x2,_) -> compare (abs (x1 - x2)) limA /= GT) . V.toList . g0 $ k
        v0    = g note0
        v1    = if isNothing note1 then V.empty
                else g . fromJust $ note1
        oberSoXSynthHelp vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
        oberSoXSynthHelp2 vec = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y $ show 0,"sine", showFFloat (Just 4) noteN $ show 0,
            "vol", showFFloat (Just 4) amplN $ show 0] "") vec
    _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
       showFFloat (Just 4) note0 $ show 0] ""
    if isNothing note1 then do
      oberSoXSynthHelp v0
    else do
      _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", showFFloat (Just 4) y $ show 0,"sine",
         showFFloat (Just 4) (fromJust note1) $ show 0] ""
      oberSoXSynthHelp v0
      oberSoXSynthHelp2 v1
    paths0 <- listDirectory "."
    let paths = sort . filter (isPrefixOf "test") $ paths0
    _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result.wav","vol","0.3"]) ""
    mapM_ removeFile paths