-- |
-- Module      :  DobutokO.Sound.Overtones
-- Copyright   :  (c) OleksandrZhabenko 2020, 2024
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- Helps to create experimental music from a file (or its part) and a Ukrainian text. 
-- It can also generate a timbre for the notes. Uses SoX inside.

{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -threaded #-}

module DobutokO.Sound.Overtones (
  -- * Library and executable functions
  -- ** For the fixed timbre
  overSoXSynthN
  -- *** For the fixed timbre with different signs for harmonics coefficients
  , overTones2
  , overSoXSynth2
  , overSoXSynthN2
  , overSoXSynthN3
  -- *** Use additional parameters
  , overSoXSynthDN
  , overSoXSynth2DN
  -- *** Use a file for information
  , overSoXSynthNGen
  , overSoXSynthNGen2
  , overSoXSynthNGen3
  -- * Extended generation using enky functionality
  -- ** With somewhat fixed timbre
  , overSoXSynthNGenE
  , overSoXSynthNGen2E
  , overSoXSynthNGen3E
  -- * New 4G functions to work with Durations
  , overSoXSynthN4G
  , overSoXSynthN24G
  , overSoXSynthN34G
  , overSoXSynthNGenE4G
  , overSoXSynthNGen2E4G
  , overSoXSynthNGen3E4G
  -- ** 4G with speech-like composition
  , overSoXSynthN4GS
  , overSoXSynthN24GS
  , overSoXSynthN34GS
  , overSoXSynthNGenE4GS
  , overSoXSynthNGen2E4GS
  , overSoXSynthNGen3E4GS
  -- * New 5G functions to work also with Intervals
  , overSoXSynthN35G
  , overSoXSynthNGen3E5G
  -- ** 5G with obtained from the text arbitraty length Intervals
  , overSoXSynthN35GS
  , overSoXSynthNGen3E5GS
  -- * New 6G function to work also with Strengths
  , overSoXSynthNGen3E6G
  -- ** 6G with obtained from the text arbitrary length Strengths
  , overSoXSynthNGen3E6GS
  , overSoXSynthNGen3E6GSu
  -- * New generalized functions working with Params
  , overSoXSynthNGenEPar
  , overSoXSynthNGenE4GSPar
  , overSoXSynthNGenE4GPar
  , overSoXSynthNGen2EPar
  , overSoXSynthNGen2E4GSPar
  , overSoXSynthNGen2E4GPar
  , overSoXSynthNGen3EPar
  , overSoXSynthNGen3E4GSPar
  , overSoXSynthNGen3E4GPar
  , overSoXSynthNGen3E5GPar
  , overSoXSynthNGen3E5GSPar
  , overSoXSynthNGen3E6GPar
  , overSoXSynthNGen3E6GSPar
  , overSoXSynthNGen3E6GSuPar
) where

import Numeric (showFFloat)
import Data.List (isPrefixOf,sort)
import Data.Maybe (isNothing,fromJust,maybe)
import qualified Data.Vector as V
import System.Process
import EndOfExe2 (showE)
import System.Directory
import Aftovolio.Ukrainian.Melodics (convertToProperUkrainianI8)
import DobutokO.Sound.Functional.Basics
import DobutokO.Sound.Functional.Params
import DobutokO.Sound.DIS5G6G

-- | For the given frequency of the note and a Ukrainian text it generates a 'V.Vector' of the tuples, each one of which contains
-- the harmonics' frequency and amplitude. The 'String' is used to produce the signs for harmonics coefficients.
overTones2 :: Float -> String -> OvertonesO
overTones2 :: Float -> String -> OvertonesO
overTones2 Float
note String
ts =
  ((Float, Float) -> Bool) -> OvertonesO -> OvertonesO
forall a. (a -> Bool) -> Vector a -> Vector a
V.takeWhile (\(!Float
w,!Float
z) -> Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Float
w (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
notes Int
107) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT Bool -> Bool -> Bool
&& Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
z) Float
0.001 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT) (OvertonesO -> OvertonesO)
-> (Vector Float -> OvertonesO) -> Vector Float -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Float, Float) -> Bool) -> OvertonesO -> OvertonesO
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (\(Float
_, Float
t4) -> Float
t4 Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/= Float
0.0) (OvertonesO -> OvertonesO)
-> (Vector Float -> OvertonesO) -> Vector Float -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    Vector Float -> Vector Float -> OvertonesO
forall a b. Vector a -> Vector b -> Vector (a, b)
V.zip (Int -> (Int -> Float) -> Vector Float
forall a. Int -> (Int -> a) -> Vector a
V.generate Int
1024 (\Int
i -> Float
note Float -> Float -> Float
forall a. Num a => a -> a -> a
* Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2))) (Vector Float -> OvertonesO) -> Vector Float -> OvertonesO
forall a b. (a -> b) -> a -> b
$ (Int -> (Int -> Float) -> Vector Float
forall a. Int -> (Int -> a) -> Vector a
V.generate Int
1024 (\Int
i -> Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Int -> Int
forall a. Vector a -> Int -> a
V.unsafeIndex (Int -> String -> Vector Int
signsFromString Int
1024 String
ts)
      (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))))

-- | Similar to 'overSoXSynth' except that takes not necessarily pure lower quint note as the second one, but the one specified by the 'String' parameter
-- as an argument to 'dNote'. If you begin the 'String' with space characters, or \"сь\", or \"ць\", or dash, or apostrophe, or soft sign, than there will
-- be no interval and the sound will be solely one with its 'OvertonesO'.
overSoXSynthDN :: Float -> String -> IO ()
overSoXSynthDN :: Float -> String -> IO ()
overSoXSynthDN Float
x = Float -> Float -> String -> IO ()
overSoXSynth2DN Float
x Float
0.5

-- | Similar to 'overSoXSynthDN' except that the resulting duration is specified by the second 'Float' parameter in seconds. For 'overSoXSynthDN'
-- it is equal to 0.5.
overSoXSynth2DN :: Float -> Float -> String -> IO ()
overSoXSynth2DN :: Float -> Float -> String -> IO ()
overSoXSynth2DN Float
x Float
y String
zs
 | [Sound8] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Sound8] -> Bool) -> (String -> [Sound8]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Sound8]
convertToProperUkrainianI8 (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ String
zs = Float -> IO ()
overSoXSynth Float
x
 | Bool
otherwise = do
    let note0 :: Float
note0 = Float -> Float
closestNote Float
x
        note1 :: Maybe Float
note1 = Int -> Float -> Maybe Float
dNote (Vector Int -> Int -> Int
forall a. Vector a -> Int -> a
V.unsafeIndex (String -> Vector Int
intervalsFromString String
zs) Int
0) Float
note0
        v0 :: OvertonesO
v0    = Float -> OvertonesO
overTones Float
note0
        v1 :: OvertonesO
v1    = OvertonesO -> (Float -> OvertonesO) -> Maybe Float -> OvertonesO
forall b a. b -> (a -> b) -> Maybe a -> b
maybe OvertonesO
forall a. Vector a
V.empty Float -> OvertonesO
overTones Maybe Float
note1
        overSoXSynthHelp :: Vector (a, a) -> IO ()
overSoXSynthHelp Vector (a, a)
vec = (Int -> (a, a) -> IO (ExitCode, String, String))
-> Vector (a, a) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !a
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
          [String
"-r22050", String
"-n", String
"test0" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
y String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"",
            String
"vol", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
amplN String
""] String
"") Vector (a, a)
vec
        overSoXSynthHelp2 :: Vector (a, a) -> IO ()
overSoXSynthHelp2 Vector (a, a)
vec = (Int -> (a, a) -> IO (ExitCode, String, String))
-> Vector (a, a) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !a
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
          [String
"-r22050", String
"-n", String
"test1" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
y String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"",
            String
"vol", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
amplN String
""] String
"") Vector (a, a)
vec
    _ <- String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testA.wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
y String
"",String
"sine",
       Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
note0 String
"", String
"vol",String
"0.5"] String
""
    if isNothing note1 then overSoXSynthHelp v0
    else do 
      _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", showFFloat (Just 4) y "","sine",
         showFFloat (Just 4) (fromJust note1) "", "vol","0.5"] ""
      overSoXSynthHelp v0
      overSoXSynthHelp2 v1
    mixTest

-- | For the given frequency it generates a musical sound with a timbre. The main component of the sound includes the lower pure quint,
-- which can be in the same octave or in the one with the number lower by one. Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The 'String' argument is used to define signs of the harmonics coefficients for Overtones.
overSoXSynth2 :: Float -> String -> IO ()
overSoXSynth2 :: Float -> String -> IO ()
overSoXSynth2 Float
x String
tts = do
  let note0 :: Float
note0 = Float -> Float
closestNote Float
x
      note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
      v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
overTones2 Float
note0 String
tts
      v1 :: OvertonesO
v1    = Float -> String -> OvertonesO
overTones2 Float
note1 String
tts
      overSoXSynthHelp :: Vector (a, a) -> IO ()
overSoXSynthHelp Vector (a, a)
vec = (Int -> (a, a) -> IO (ExitCode, String, String))
-> Vector (a, a) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !a
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
        [String
"-r22050", String
"-n", String
"test0" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"",
           String
"vol", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
amplN String
""] String
"") Vector (a, a)
vec
      overSoXSynthHelp2 :: Vector (a, a) -> IO ()
overSoXSynthHelp2 Vector (a, a)
vec = (Int -> (a, a) -> IO (ExitCode, String, String))
-> Vector (a, a) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !a
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
        [String
"-r22050", String
"-n", String
"test1" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"",
           String
"vol", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
amplN String
""] String
"") Vector (a, a)
vec
  _ <- String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"test01.wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
note0 String
"",
     String
"synth", String
"0.5",String
"sine", String
"mix", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
note1 String
"", String
"vol",String
"0.5"] String
""
  overSoXSynthHelp v0
  overSoXSynthHelp2 v1
  mixTest 

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Float' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
overSoXSynthN :: Int -> Float -> Float -> String -> V.Vector Float -> IO ()
overSoXSynthN :: Int -> Float -> Float -> String -> Vector Float -> IO ()
overSoXSynthN Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Vector Float -> Vector Float -> IO ()
overSoXSynthN4G Int
n Float
ampL (Int -> String -> Float -> Vector Float
str2DurationsDef Int
n String
zs Float
time3)

-- | Function to create a melody for the given arguments. 'Durations' is used to provide a rhythm. 
overSoXSynthN4G :: Int -> Float -> Durations -> V.Vector Float -> IO ()
overSoXSynthN4G :: Int -> Float -> Vector Float -> Vector Float -> IO ()
overSoXSynthN4G Int
n Float
ampL Vector Float
v2 Vector Float
vec0
 | (Float -> Bool) -> Vector Float -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Vector Float
v2 = String -> IO ()
putStrLn String
"You provided no valid durations data! "
 | Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
0.01 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT Bool -> Bool -> Bool
&& Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
1.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT = 
    let zeroN :: Int
zeroN = Vector Float -> Int
forall a. Vector a -> Int
numVZeroesPre Vector Float
vec0
        v21 :: Vector Float
v21 = (Float -> Bool) -> Vector Float -> Vector Float
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/=Float
0.0) Vector Float
v2
        m :: Int
m = Vector Float -> Int
forall a. Vector a -> Int
V.length Vector Float
v2 in (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
j Float
x -> do 
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x                     -- zs is obtained from the command line arguments
              note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
              v0 :: OvertonesO
v0    = Float -> OvertonesO
overTones Float
note0
              v1 :: OvertonesO
v1    = Float -> OvertonesO
overTones Float
note1
              overSoXSynthHelpN :: Vector (a, Float) -> IO ()
overSoXSynthHelpN Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"test" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec
              overSoXSynthHelpN2 :: Vector (a, Float) -> IO ()
overSoXSynthHelpN2 Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"testQ" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec  
              soxSynthHelpMain :: a -> a -> IO (ExitCode, String, String)
soxSynthHelpMain a
note01 a
note02 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testA" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"", String
"synth",
                  Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", String
"mix", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"", String
"vol",if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT 
                    then String
"0.5" else String
"0"] String
""
          _ <- Float -> Float -> IO (ExitCode, String, String)
forall {a} {a}.
(RealFloat a, RealFloat a) =>
a -> a -> IO (ExitCode, String, String)
soxSynthHelpMain Float
note0 Float
note1
          overSoXSynthHelpN v0
          overSoXSynthHelpN2 v1
          mixTest2 zeroN j) Vector Float
vec0
 | Bool
otherwise = let ampL1 :: Float
ampL1 = Float
ampL Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Integer
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ Float
ampL) in
    if Float -> Float
forall a. Num a => a -> a
abs Float
ampL1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0.01 then Int -> Float -> Vector Float -> Vector Float -> IO ()
overSoXSynthN4G Int
n Float
0.01 Vector Float
v2 Vector Float
vec0
    else Int -> Float -> Vector Float -> Vector Float -> IO ()
overSoXSynthN4G Int
n Float
ampL1 Vector Float
v2 Vector Float
vec0

-- | Variant of the 'overSoXSynthN4G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
overSoXSynthN4GS :: Int -> Float -> Float -> String -> V.Vector Float -> IO ()
overSoXSynthN4GS :: Int -> Float -> Float -> String -> Vector Float -> IO ()
overSoXSynthN4GS Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Vector Float -> Vector Float -> IO ()
overSoXSynthN4G Int
n Float
ampL (String -> Float -> Vector Float
str2Durations String
zs Float
time3)

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Float' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
overSoXSynthN2 :: Int -> Float -> Float -> String -> String -> V.Vector Float -> IO ()
overSoXSynthN2 :: Int -> Float -> Float -> String -> String -> Vector Float -> IO ()
overSoXSynthN2 Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Vector Float -> String -> Vector Float -> IO ()
overSoXSynthN24G Int
n Float
ampL (Int -> String -> Float -> Vector Float
str2DurationsDef Int
n String
zs Float
time3)
 
-- | Function to create a melody for the given arguments. 'Durations' is used to provide a rhythm. 
overSoXSynthN24G :: Int -> Float -> Durations -> String -> V.Vector Float -> IO ()
overSoXSynthN24G :: Int -> Float -> Vector Float -> String -> Vector Float -> IO ()
overSoXSynthN24G Int
n Float
ampL Vector Float
v2 String
tts Vector Float
vec0
 | (Float -> Bool) -> Vector Float -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Vector Float
v2 = String -> IO ()
putStrLn String
"You provided no valid durations data! "
 | Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
0.01 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT Bool -> Bool -> Bool
&& Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
1.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT = 
    let v21 :: Vector Float
v21 = (Float -> Bool) -> Vector Float -> Vector Float
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/= Float
0.0) Vector Float
v2
        zeroN :: Int
zeroN = Vector Float -> Int
forall a. Vector a -> Int
numVZeroesPre Vector Float
vec0
        m :: Int
m = Vector Float -> Int
forall a. Vector a -> Int
V.length Vector Float
v21 in (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
j Float
x -> do 
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x                     -- zs is obtained from the command line arguments
              note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
overTones2 Float
note0 String
tts
              v1 :: OvertonesO
v1    = Float -> String -> OvertonesO
overTones2 Float
note1 String
tts
              overSoXSynthHelpN :: Vector (a, Float) -> IO ()
overSoXSynthHelpN Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"test" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                  String
"sine",Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec
              overSoXSynthHelpN2 :: Vector (a, Float) -> IO ()
overSoXSynthHelpN2 Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"testQ" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec  
              soxSynthHelpMain :: a -> a -> IO (ExitCode, String, String)
soxSynthHelpMain a
note01 a
note02 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testA" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"",
                  String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", String
"mix", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"", String
"vol",
                     if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then String
"0.5" else String
"0"] String
""
          _ <- Float -> Float -> IO (ExitCode, String, String)
forall {a} {a}.
(RealFloat a, RealFloat a) =>
a -> a -> IO (ExitCode, String, String)
soxSynthHelpMain Float
note0 Float
note1
          overSoXSynthHelpN v0
          overSoXSynthHelpN2 v1
          mixTest2 zeroN j) Vector Float
vec0
 | Bool
otherwise = let ampL1 :: Float
ampL1 = Float
ampL Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Integer
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ Float
ampL) in
    if Float -> Float
forall a. Num a => a -> a
abs Float
ampL1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0.01 then Int -> Float -> Vector Float -> String -> Vector Float -> IO ()
overSoXSynthN24G Int
n Float
0.01 Vector Float
v2 String
tts Vector Float
vec0
    else Int -> Float -> Vector Float -> String -> Vector Float -> IO ()
overSoXSynthN24G Int
n Float
ampL1 Vector Float
v2 String
tts Vector Float
vec0        

-- | Variant of the 'overSoXSynthN24G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
overSoXSynthN24GS :: Int -> Float -> Float -> String -> String -> V.Vector Float -> IO ()
overSoXSynthN24GS :: Int -> Float -> Float -> String -> String -> Vector Float -> IO ()
overSoXSynthN24GS Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Vector Float -> String -> Vector Float -> IO ()
overSoXSynthN24G Int
n Float
ampL (String -> Float -> Vector Float
str2Durations String
zs Float
time3)

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Float' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The third 'String' argument is used to define the intervals for the notes if any.
-- The third 'Float' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is experimental feature.
overSoXSynthN3 :: Int -> Float -> Float -> Float -> String -> String -> String -> V.Vector Float -> IO ()
overSoXSynthN3 :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN3 Int
n Float
ampL Float
time3 Float
dAmpl String
zs = Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34G Int
n Float
ampL Float
dAmpl (Int -> String -> Float -> Vector Float
str2DurationsDef Int
n String
zs Float
time3)

-- | Function to create a melody for the given arguments. 'Duraitons' is used to provide a rhythm. 
overSoXSynthN34G :: Int -> Float -> Float -> Durations -> String -> String -> V.Vector Float -> IO ()
overSoXSynthN34G :: Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34G Int
n Float
ampL Float
dAmpl Vector Float
v2 String
tts String
vs Vector Float
vec0
 | (Float -> Bool) -> Vector Float -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Vector Float
v2 = String -> IO ()
putStrLn String
"You provided no valid durations data! "
 | Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
0.01 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT Bool -> Bool -> Bool
&& Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
1.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT = 
    let v21 :: Vector Float
v21 = (Float -> Bool) -> Vector Float -> Vector Float
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/= Float
0.0) Vector Float
v2
        m :: Int
m     = Vector Float -> Int
forall a. Vector a -> Int
V.length Vector Float
v21
        zeroN :: Int
zeroN = Vector Float -> Int
forall a. Vector a -> Int
numVZeroesPre Vector Float
vec0
        v3 :: Vector Int
v3    = String -> Vector Int
intervalsFromString String
vs
        l :: Int
l     = String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
vs in (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
j Float
x -> do 
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x                     -- zs is obtained from the command line arguments
              note1 :: Maybe Float
note1 = Int -> Float -> Maybe Float
dNote (Vector Int -> Int -> Int
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Int
v3 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
l)) Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
overTones2 Float
note0 String
tts
              v1 :: OvertonesO
v1    = if Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
note1 then OvertonesO
forall a. Vector a
V.empty
                      else Float -> String -> OvertonesO
overTones2 (Maybe Float -> Float
forall a. HasCallStack => Maybe a -> a
fromJust Maybe Float
note1) String
tts
              overSoXSynthHelpN :: Vector (a, Float) -> IO ()
overSoXSynthHelpN Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"test" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                  String
"sine",Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec
              overSoXSynthHelpN2 :: Vector (a, Float) -> IO ()
overSoXSynthHelpN2 Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"testQ" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (if Float
dAmpl Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
1.0 then Float
1.0
                     else Float
dAmpl Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec  
              soxSynthHelpMain0 :: a -> IO (ExitCode, String, String)
soxSynthHelpMain0 a
note01 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testA" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++  String
".wav",
                String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"", String
"vol",
                  if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then String
"0.5" else String
"0"] String
""
              soxSynthHelpMain1 :: a -> IO (ExitCode, String, String)
soxSynthHelpMain1 a
note02 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testB" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                 Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"",
                   String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (if Float
dAmpl Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.5 then Float
0.5 else Float
dAmpl Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2) String
"" else String
"0"] String
""
          if Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
note1 then do { _ <- Float -> IO (ExitCode, String, String)
forall {a}. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                                     ; overSoXSynthHelpN v0 }
          else do { _ <- Float -> IO (ExitCode, String, String)
forall {a}. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                  ; _ <- soxSynthHelpMain1 (fromJust note1)
                  ; overSoXSynthHelpN v0
                  ; overSoXSynthHelpN2 v1}
          paths0 <- String -> IO [String]
listDirectory String
"."
          let paths = [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf String
"test") ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
paths0
          _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result0" ++ prependZeroes zeroN (show j) ++ ".wav","vol","0.3"]) ""
          mapM_ removeFile paths) Vector Float
vec0
 | Bool
otherwise = let ampL1 :: Float
ampL1 = Float
ampL Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Integer
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ Float
ampL) in
    if Float -> Float
forall a. Num a => a -> a
abs Float
ampL1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0.01 then Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34G Int
n Float
0.01 Float
dAmpl Vector Float
v2 String
tts String
vs Vector Float
vec0
    else Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34G Int
n Float
ampL1 Float
dAmpl Vector Float
v2 String
tts String
vs Vector Float
vec0

-- | Generalized variant of the 'overSoXSynthN34G' where you specify your own 'Intervals'. For more information, please, refer to 'intervalsFromStringG'.
overSoXSynthN35G :: Int -> Float -> Float -> Durations -> String -> Intervals -> V.Vector Float -> IO ()
overSoXSynthN35G :: Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> IO ()
overSoXSynthN35G Int
n Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 Vector Float
vec0
 | (Float -> Bool) -> Vector Float -> Bool
forall a. (a -> Bool) -> Vector a -> Bool
V.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Vector Float
v2 = String -> IO ()
putStrLn String
"You provided no valid durations data! "
 | Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
0.01 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT Bool -> Bool -> Bool
&& Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Float -> Float
forall a. Num a => a -> a
abs Float
ampL) Float
1.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT = 
    let v21 :: Vector Float
v21 = (Float -> Bool) -> Vector Float -> Vector Float
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/=Float
0.0) Vector Float
v2
        m :: Int
m     = Vector Float -> Int
forall a. Vector a -> Int
V.length Vector Float
v21
        zeroN :: Int
zeroN = Vector Float -> Int
forall a. Vector a -> Int
numVZeroesPre Vector Float
vec0
        l :: Int
l     = Vector Int -> Int
forall a. Vector a -> Int
V.length Vector Int
v3 in (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
j Float
x -> do 
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x                     -- zs is obtained from the command line arguments
              note1 :: Maybe Float
note1 = Int -> Float -> Maybe Float
dNote (Vector Int -> Int -> Int
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Int
v3 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
l)) Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
overTones2 Float
note0 String
tts
              v1 :: OvertonesO
v1    = if Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
note1 then OvertonesO
forall a. Vector a
V.empty
                      else Float -> String -> OvertonesO
overTones2 (Maybe Float -> Float
forall a. HasCallStack => Maybe a -> a
fromJust Maybe Float
note1) String
tts
              overSoXSynthHelpN :: Vector (a, Float) -> IO ()
overSoXSynthHelpN Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"test" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                  String
"sine",Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec
              overSoXSynthHelpN2 :: Vector (a, Float) -> IO ()
overSoXSynthHelpN2 Vector (a, Float)
vec = (Int -> (a, Float) -> IO (ExitCode, String, String))
-> Vector (a, Float) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
V.imapM_ (\Int
i (a
noteN, !Float
amplN) -> String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox"))
                [String
"-r22050", String
"-n", String
"testQ" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
noteN String
"", String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (if Float
dAmpl Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
1.0 then Float
1.0
                     else Float
dAmpl Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
amplN Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
ampL) String
"" else String
"0"] String
"") Vector (a, Float)
vec  
              soxSynthHelpMain0 :: a -> IO (ExitCode, String, String)
soxSynthHelpMain0 a
note01 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testA" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++  String
".wav",
                String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"", String
"vol",
                  if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then String
"0.5" else String
"0"] String
""
              soxSynthHelpMain1 :: a -> IO (ExitCode, String, String)
soxSynthHelpMain1 a
note02 = String -> [String] -> String -> IO (ExitCode, String, String)
readProcessWithExitCode (Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust (String -> Maybe String
showE String
"sox")) [String
"-r22050", String
"-n", String
"testB" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                 Int -> String -> String
prependZeroes Int
zeroN String
"1" String -> String -> String
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"",
                   String
"vol", if Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Vector Float -> Int -> Float
forall a. Vector a -> Int -> a
V.unsafeIndex Vector Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) Float
0.0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT then Maybe Int -> Float -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (if Float
dAmpl Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.5 then Float
0.5 else Float
dAmpl Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
2) String
"" else String
"0"] String
""
          if Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
note1 then do { _ <- Float -> IO (ExitCode, String, String)
forall {a}. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                                     ; overSoXSynthHelpN v0 }
          else do { _ <- Float -> IO (ExitCode, String, String)
forall {a}. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                  ; _ <- soxSynthHelpMain1 (fromJust note1)
                  ; overSoXSynthHelpN v0
                  ; overSoXSynthHelpN2 v1}
          paths0 <- String -> IO [String]
listDirectory String
"."
          let paths = [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf String
"test") ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
paths0
          _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result0" ++ prependZeroes zeroN (show j) ++ ".wav","vol","0.3"]) ""
          mapM_ removeFile paths) Vector Float
vec0
 | Bool
otherwise = let ampL1 :: Float
ampL1 = Float
ampL Float -> Float -> Float
forall a. Num a => a -> a -> a
- (Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Float) -> (Float -> Integer) -> Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Integer
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Float -> Float) -> Float -> Float
forall a b. (a -> b) -> a -> b
$ Float
ampL) in
    if Float -> Float
forall a. Num a => a -> a
abs Float
ampL1 Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0.01 then Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> IO ()
overSoXSynthN35G Int
n Float
0.01 Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 Vector Float
vec0
    else Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> IO ()
overSoXSynthN35G Int
n Float
ampL1 Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 Vector Float
vec0

-- | Variant of the 'overSoXSynthN34G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
overSoXSynthN34GS :: Int -> Float -> Float -> Float -> String -> String -> String -> V.Vector Float -> IO ()
overSoXSynthN34GS :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34GS Int
n Float
ampL Float
time3 Float
dAmpl String
zs = Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> Vector Float
-> IO ()
overSoXSynthN34G Int
n Float
ampL Float
dAmpl (String -> Float -> Vector Float
str2Durations String
zs Float
time3)

-- | Variant of the 'overSoXSynthN34G' where intervals are obtained from the basic 'Intervals' with the length no more than 29 and a Ukrainian text 
-- specified as the last 'String' argument so that you can produce 'Intervals' of the arbitrary length. For more information, please, refer to 
-- 'intervalsFromStringG' and 'strToIntG'.
overSoXSynthN35GS :: Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> V.Vector Float -> IO ()
overSoXSynthN35GS :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> Vector Int
-> String
-> Vector Float
-> IO ()
overSoXSynthN35GS Int
n Float
ampL Float
time3 Float
dAmpl String
zs String
tts Vector Int
v3 String
vs = Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> IO ()
overSoXSynthN35G Int
n Float
ampL Float
dAmpl (String -> Float -> Vector Float
str2Durations String
zs Float
time3) String
tts (Vector Int -> String -> Vector Int
intervalsFromStringG Vector Int
v3 String
vs)

-- | Similar to 'overSoXSynthN', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Float' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
--
-- For better usage the 'FilePath' should be a filepath for the .wav file.
overSoXSynthNGen :: FilePath -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGen :: String -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGen String
file Int
m = String -> Int -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGenE String
file Int
m Int
12
  
-- | Similar to 'overSoXSynthNGen', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGenE :: FilePath -> Int -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGenE :: String -> Int -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGenE String
file Int
m Int
ku Float
ampL Float
time3 String
zs = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4Gi n file m ku ampL (str2DurationsDef n zs time3)

-- | Generalized version of the 'overSoXSynthNGenE' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGenEPar :: FilePath -> Params -> Float -> Float -> String -> IO ()
overSoXSynthNGenEPar :: String -> Params -> Float -> Float -> String -> IO ()
overSoXSynthNGenEPar String
file Params
params Float
ampL Float
time3 String
zs = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4GiPar n file params ampL (str2DurationsDef n zs time3)

-- | Variant of the 'overSoXSynthNGenE4G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
overSoXSynthNGenE4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGenE4GS :: String -> Int -> Int -> Float -> Float -> String -> IO ()
overSoXSynthNGenE4GS String
file Int
m Int
ku Float
ampL Float
time3 String
zs = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4Gi n file m ku ampL (str2Durations zs time3)

-- | Generalized version of the 'overSoXSynthNGenE4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGenE4GSPar :: FilePath -> Params -> Float -> Float -> String -> IO ()
overSoXSynthNGenE4GSPar :: String -> Params -> Float -> Float -> String -> IO ()
overSoXSynthNGenE4GSPar String
file Params
params Float
ampL Float
time3 String
zs = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4GiPar n file params ampL (str2Durations zs time3)  

-- | Note that the last two 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The third 'Int' parameter defines that @n@.
nGenE4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> IO ()
nGenE4Gi :: Int -> String -> Int -> Int -> Float -> Vector Float -> IO ()
nGenE4Gi Int
n String
file Int
m Int
ku Float
ampL Vector Float
v2 = do
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Int -> Int -> Vector Float -> Vector Float
liftInEnkuV Int
m Int
ku (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float)
-> (Vector Int -> Vector Int) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> Vector Int -> Vector Int
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN4G n ampL v2 vecB
  endFromResult  
    
-- | Generalized version of the 'nGenE4Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
nGenE4GiPar :: Int -> FilePath -> Params -> Float -> Durations -> IO ()
nGenE4GiPar :: Int -> String -> Params -> Float -> Vector Float -> IO ()
nGenE4GiPar Int
n String
file Params
params Float
ampL Vector Float
v2 = do
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Params -> Vector Float -> Vector Float
liftInParamsV Params
params (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN4G n ampL v2 vecB
  endFromResult      
       
-- | 4G genaralized version of the 'overSoXSynthNGenE' where you provide your own 'Durations'.
overSoXSynthNGenE4G :: FilePath -> Int -> Int -> Float -> Durations -> IO ()
overSoXSynthNGenE4G :: String -> Int -> Int -> Float -> Vector Float -> IO ()
overSoXSynthNGenE4G String
file Int
m Int
ku Float
ampL Vector Float
v2 = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4Gi n file m ku ampL v2

-- | Generalized version of the 'overSoXSynthNGenE4G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGenE4GPar :: FilePath -> Params -> Float -> Durations -> IO ()
overSoXSynthNGenE4GPar :: String -> Params -> Float -> Vector Float -> IO ()
overSoXSynthNGenE4GPar String
file Params
params Float
ampL Vector Float
v2 = do
  n <- String -> IO Int
duration1000 String
file
  nGenE4GiPar n file params ampL v2  

-- | Similar to 'overSoXSynthN2', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Float' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
-- 
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The second 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
overSoXSynthNGen2 :: FilePath -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2 :: String -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2 String
file Int
m = String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E String
file Int
m Int
12
  
-- | Similar to 'overSoXSynthNGen2', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen2'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGen2E :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E :: String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4Gi n file m ku ampL (str2DurationsDef n zs time3) tts

-- | Generalized version of the 'overSoXSynthNGen2E' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen2EPar :: FilePath -> Params -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2EPar :: String -> Params -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2EPar String
file Params
params Float
ampL Float
time3 String
zs String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4GiPar n file params ampL (str2DurationsDef n zs time3) tts  

-- | Variant of the 'overSoXSynthNGen2E4G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
overSoXSynthNGen2E4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E4GS :: String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E4GS String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4Gi n file m ku ampL (str2Durations zs time3) tts

-- | Generalized version of the 'overSoXSynthNGen2E4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen2E4GSPar :: FilePath -> Params -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E4GSPar :: String -> Params -> Float -> Float -> String -> String -> IO ()
overSoXSynthNGen2E4GSPar String
file Params
params Float
ampL Float
time3 String
zs String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4GiPar n file params ampL (str2Durations zs time3) tts

-- | Note that the last two 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The third 'Int' parameter defines that @n@.
nGen2E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
nGen2E4Gi :: Int
-> String -> Int -> Int -> Float -> Vector Float -> String -> IO ()
nGen2E4Gi Int
n String
file Int
m Int
ku Float
ampL Vector Float
v2 String
tts = do
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Int -> Int -> Vector Float -> Vector Float
liftInEnkuV Int
m Int
ku (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float)
-> (Vector Int -> Vector Int) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> Vector Int -> Vector Int
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN24G n ampL v2 tts vecB
  endFromResult 

-- | Generalized version of the 'nGen2E4Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
nGen2E4GiPar :: Int -> FilePath -> Params -> Float -> Durations -> String -> IO ()
nGen2E4GiPar :: Int -> String -> Params -> Float -> Vector Float -> String -> IO ()
nGen2E4GiPar Int
n String
file Params
params Float
ampL Vector Float
v2 String
tts = do
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Params -> Vector Float -> Vector Float
liftInParamsV Params
params (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN24G n ampL v2 tts vecB
  endFromResult   
       
-- | 4G genaralized version of the 'overSoXSynthNGen2E' where you provide your own 'Durations'.
overSoXSynthNGen2E4G :: FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
overSoXSynthNGen2E4G :: String -> Int -> Int -> Float -> Vector Float -> String -> IO ()
overSoXSynthNGen2E4G String
file Int
m Int
ku Float
ampL Vector Float
v2 String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4Gi n file m ku ampL v2 tts

-- | Generalized version of the 'overSoXSynthNGen2E4G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen2E4GPar :: FilePath -> Params -> Float -> Durations -> String -> IO ()
overSoXSynthNGen2E4GPar :: String -> Params -> Float -> Vector Float -> String -> IO ()
overSoXSynthNGen2E4GPar String
file Params
params Float
ampL Vector Float
v2 String
tts = do
  n <- String -> IO Int
duration1000 String
file
  nGen2E4GiPar n file params ampL v2 tts  

-- | Similar to 'overSoXSynthN2', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Float' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Float' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
-- 
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The second 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
-- The third 'String' argument is used to define the intervals for the notes if any.
-- The third 'Float' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is experimental feature.
overSoXSynthNGen3 :: FilePath -> Int -> Float -> Float -> Float -> String -> String -> String -> IO ()
overSoXSynthNGen3 :: String
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3 String
file Int
m = String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3E String
file Int
m Int
12
  
-- | Similar to 'overSoXSynthNGen3', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen3'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGen3E :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> IO ()
overSoXSynthNGen3E :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3E String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4Gi n file m ku ampL dAmpl (str2DurationsDef n zs time3) tts vs

-- | Generalized version of the 'overSoXSynthNGen3E' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3EPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> IO ()
overSoXSynthNGen3EPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3EPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
zs String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4GiPar n file params ampL dAmpl (str2DurationsDef n zs time3) tts vs  

-- | Variant of the 'overSoXSynthNGen3E4G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E4GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> IO ()
overSoXSynthNGen3E4GS :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3E4GS String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4Gi n file m ku ampL dAmpl (str2Durations zs time3) tts vs 

-- | Generalized version of the 'overSoXSynthNGen3E4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E4GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> IO ()
overSoXSynthNGen3E4GSPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
overSoXSynthNGen3E4GSPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
zs String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4GiPar n file params ampL dAmpl (str2Durations zs time3) tts vs    

-- | Note that the last two 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The third 'Int' parameter defines that @n@.
nGen3E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> IO ()
nGen3E4Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> IO ()
nGen3E4Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts String
vs = do 
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Int -> Int -> Vector Float -> Vector Float
liftInEnkuV Int
m Int
ku (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float)
-> (Vector Int -> Vector Int) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> Vector Int -> Vector Int
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN34G n ampL dAmpl v2 tts vs vecB
  endFromResult  

-- | Generalized version of the 'nGen3E4Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
nGen3E4GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> String -> IO ()
nGen3E4GiPar :: Int
-> String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> String
-> IO ()
nGen3E4GiPar Int
n String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts String
vs = do 
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Params -> Vector Float -> Vector Float
liftInParamsV Params
params (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN34G n ampL dAmpl v2 tts vs vecB
  endFromResult    

-- | Note that the last two 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The third 'Int' parameter defines that @n@.
nGen3E5Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> Intervals -> IO ()
nGen3E5Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
nGen3E5Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 = do 
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Int -> Int -> Vector Float -> Vector Float
liftInEnkuV Int
m Int
ku (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float)
-> (Vector Int -> Vector Int) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> Vector Int -> Vector Int
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN35G n ampL dAmpl v2 tts v3 vecB
  endFromResult  
    
-- | Generalized version of the 'nGen3E5Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
nGen3E5GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> Intervals -> IO ()
nGen3E5GiPar :: Int
-> String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
nGen3E5GiPar Int
n String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 = do 
  vecA <- String -> Int -> IO (Vector Int)
freqsFromFile String
file Int
n
  let vecB = Params -> Vector Float -> Vector Float
liftInParamsV Params
params (Vector Float -> Vector Float)
-> (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> Vector a -> Vector b
V.map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Int -> Vector Float) -> Vector Int -> Vector Float
forall a b. (a -> b) -> a -> b
$ Vector Int
vecA
  overSoXSynthN35G n ampL dAmpl v2 tts v3 vecB
  endFromResult      

-- | 4G generalized function for 'overSoXSynthNGen3E' where you provide your own 'Durations'. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E4G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> IO ()
overSoXSynthNGen3E4G :: String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> String
-> IO ()
overSoXSynthNGen3E4G String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4Gi n file m ku ampL dAmpl v2 tts vs

-- | Generalized version of the 'overSoXSynthNGen3E4G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E4GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> String -> IO ()
overSoXSynthNGen3E4GPar :: String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> String
-> IO ()
overSoXSynthNGen3E4GPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E4GiPar n file params ampL dAmpl v2 tts vs  

-- | 5G generalized function for 'overSoXSynthNGen3E4G' where you provide your own 'Intervals'. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E5G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> Intervals -> IO ()
overSoXSynthNGen3E5G :: String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
overSoXSynthNGen3E5G String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E5Gi n file m ku ampL dAmpl v2 tts v3 

-- | Generalized version of the 'overSoXSynthNGen3E5G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E5GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> Intervals -> IO ()
overSoXSynthNGen3E5GPar :: String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
overSoXSynthNGen3E5GPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E5GiPar n file params ampL dAmpl v2 tts v3    

-- | Variant of the 'overSoXSynthNGen3E5G' where 'Intervals' are obtained from the basic 'Intervals' with the length no more than 29 and a Ukrainian text 
-- specified as the last 'String' argument so that you can produce 'Intervals' of the arbitrary length. For more information, please, refer to 
-- 'intervalsFromStringG' and 'strToIntG'. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E5GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> IO ()
overSoXSynthNGen3E5GS :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> Vector Int
-> String
-> IO ()
overSoXSynthNGen3E5GS String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
tts Vector Int
v3 String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E5Gi n file m ku ampL dAmpl (str2Durations zs time3) tts (intervalsFromStringG v3 vs)

-- | Generalized version of the 'overSoXSynthNGen3E5GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E5GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> Intervals -> String -> IO ()
overSoXSynthNGen3E5GSPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> Vector Int
-> String
-> IO ()
overSoXSynthNGen3E5GSPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
zs String
tts Vector Int
v3 String
vs = do
  n <- String -> IO Int
duration1000 String
file
  nGen3E5GiPar n file params ampL dAmpl (str2Durations zs time3) tts (intervalsFromStringG v3 vs)  
  
-- | 6G generalized function for 'overSoXSynthNGen3E5G' where you provide your own 'Strengths'. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E6G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> Intervals -> Strengths -> Float -> IO ()
overSoXSynthNGen3E6G :: String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6G String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 Vector Float
v6 Float
limV = 
 String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
overSoXSynthNGen3E5G String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Vector Float -> String -> String -> Float -> IO ()
apply6G2 Vector Float
v6 String
"221w" String
"result" Float
limV IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
endFromResult

-- | Generalized version of the 'overSoXSynthNGen3E6G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E6GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> Intervals -> Strengths -> Float -> IO ()
overSoXSynthNGen3E6GPar :: String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6GPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 Vector Float
v6 Float
limV = 
 String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> IO ()
overSoXSynthNGen3E5GPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Vector Float -> String -> String -> Float -> IO ()
apply6G2 Vector Float
v6 String
"221w" String
"result" Float
limV IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
endFromResult 

-- | A variant of 'overSoXSynthNGen3E6G' where 'Strengths' are obtained from a Ukrainian text specified as the last 'String' argument. Note that 'Int' arguments are used by 'liftInEnku' in that order so it 
-- returns a 'Maybe' number (actually frequency) for the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E6GS :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> Intervals -> String -> Float -> IO ()
overSoXSynthNGen3E6GS :: String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> String
-> Float
-> IO ()
overSoXSynthNGen3E6GS String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 String
xxs Float
limV = String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6G String
file Int
m Int
ku Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 (String -> Vector Float
str2Volume String
xxs) Float
limV

-- | Generalized version of the 'overSoXSynthNGen3E6GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E6GSPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> Intervals -> String -> Float -> IO ()
overSoXSynthNGen3E6GSPar :: String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> String
-> Float
-> IO ()
overSoXSynthNGen3E6GSPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 String
xxs Float
limV = String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6GPar String
file Params
params Float
ampL Float
dAmpl Vector Float
v2 String
tts Vector Int
v3 (String -> Vector Float
str2Volume String
xxs) Float
limV

-- | A variant of 'overSoXSynthNGen3E6GS' where 'Strengths' and 'Durations' are obtained from the same Ukrainian text specified as 
-- the last 'String' argument. The third 'Float' argument is an average duration of the sounds in seconds. 
-- Note that 'Int' arguments are used by 'liftInEnku' in that order so it returns a 'Maybe' number (actually frequency) for 
-- the n-th elements set of notes (see 'nkyT'). The second 'Int' parameter defines that @n@.
overSoXSynthNGen3E6GSu :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> Intervals -> String -> Float -> IO ()
overSoXSynthNGen3E6GSu :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> Vector Int
-> String
-> Float
-> IO ()
overSoXSynthNGen3E6GSu String
file Int
m Int
ku Float
ampL Float
dAmpl Float
time3 String
tts Vector Int
v3 String
xxs = String
-> Int
-> Int
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6G String
file Int
m Int
ku Float
ampL Float
dAmpl (String -> Float -> Vector Float
str2Durations String
xxs Float
time3) String
tts Vector Int
v3 (String -> Vector Float
str2Volume String
xxs)

-- | Generalized version of the 'overSoXSynthNGen3E6GSu' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
overSoXSynthNGen3E6GSuPar :: FilePath -> Params -> Float -> Float -> Float -> String -> Intervals -> String -> Float -> IO ()
overSoXSynthNGen3E6GSuPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> Vector Int
-> String
-> Float
-> IO ()
overSoXSynthNGen3E6GSuPar String
file Params
params Float
ampL Float
dAmpl Float
time3 String
tts Vector Int
v3 String
xxs = String
-> Params
-> Float
-> Float
-> Vector Float
-> String
-> Vector Int
-> Vector Float
-> Float
-> IO ()
overSoXSynthNGen3E6GPar String
file Params
params Float
ampL Float
dAmpl (String -> Float -> Vector Float
str2Durations String
xxs Float
time3) String
tts Vector Int
v3 (String -> Vector Float
str2Volume String
xxs)