-- |
-- Module      :  Composition.Sound.Uniq
-- Copyright   :  (c) OleksandrZhabenko 2020-2021
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@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 #-}
{-# OPTIONS_HADDOCK show-extensions #-}

module Composition.Sound.Uniq (
  -- * Library and executable functions
  -- ** For the unique for the String structure timbre
  uniqOvertonesV
  , uniqOverSoXSynth
  , uniqOverSoXSynthN
  -- *** For the unique for the String structure timbre with different signs for harmonics coefficients
  , uniqOvertonesV2
  , uniqOverSoXSynth2
  , uniqOverSoXSynthN3
  , uniqOverSoXSynthN4
  -- *** Use a file for information
  , uniqOverSoXSynthNGen
  , uniqOverSoXSynthNGen3
  , uniqOverSoXSynthNGen4
  -- * Extended generation using enky functionality
 -- ** With usage of additional information in the Ukrainian text
  , uniqOverSoXSynthNGenE
  , uniqOverSoXSynthNGen3E
  , uniqOverSoXSynthNGen4E
  -- * New 4G functions to work with Durations
  , uniqOverSoXSynthN4G
  , uniqOverSoXSynthN34G
  , uniqOverSoXSynthN44G
  , uniqOverSoXSynthNGenE4G
  , uniqOverSoXSynthNGen3E4G
  , uniqOverSoXSynthNGen4E4G
  -- ** 4G with speech-like composition
  , uniqOverSoXSynthN4GS
  , uniqOverSoXSynthN34GS
  , uniqOverSoXSynthN44GS
  , uniqOverSoXSynthNGenE4GS
  , uniqOverSoXSynthNGen3E4GS
  , uniqOverSoXSynthNGen4E4GS
  -- * New 5G functions to work also with Intervals
  , uniqOverSoXSynthN45G
  , uniqOverSoXSynthNGen4E5G
  -- ** 5G with obtained from the text arbitraty length Intervals
  , uniqOverSoXSynthN45GS
  , uniqOverSoXSynthNGen4E5GS
  -- * New 6G function to work also with Strengths
  , uniqOverSoXSynthNGen4E6G
  -- ** 6G with obtained from the text arbitrary length Strengths
  , uniqOverSoXSynthN46GS
  , uniqOverSoXSynthN46GSu
  , uniqOverSoXSynthNGen4E6GS
  , uniqOverSoXSynthNGen4E6GSu
  -- ** With overtones obtained from the additional Ukrainian text
  , uniqOverSoXSynthNGenEPar
  , uniqOverSoXSynthNGenE4GSPar
  , uniqOverSoXSynthNGenE4GPar
  , uniqOverSoXSynthNGen3EPar
  , uniqOverSoXSynthNGen3E4GSPar
  , uniqOverSoXSynthNGen3E4GPar
  , uniqOverSoXSynthNGen4EPar
  , uniqOverSoXSynthNGen4E4GSPar
  , uniqOverSoXSynthNGen4E4GPar
  , uniqOverSoXSynthNGen4E5GPar
  , uniqOverSoXSynthNGen4E5GSPar
  , uniqOverSoXSynthNGen4E6GPar
  , uniqOverSoXSynthNGen4E6GSPar
  , uniqOverSoXSynthNGen4E6GSuPar
) where

import Numeric (showFFloat)
import Data.Maybe (isNothing,fromJust)
import GHC.Arr
import qualified Data.Foldable as F
import Data.Foldable.Ix
import System.Process
import EndOfExe (showE)
import Phonetic.Languages.UniquenessPeriodsG
import Composition.Sound.Functional.Basics
import Composition.Sound.Functional.Params
import Composition.Sound.DIS5G6G

-- | For the given frequency of the note it generates a list of the tuples, each one of which contains the harmonics' frequency and amplitude. For every given
-- 'String' structure of the uniqueness (see the documentation for @ukrainian-phonetics-basic-array@ and @uniqueness-periods@ packages) it produces the unique timbre.
-- Partial function.
uniqOvertonesV :: Float -> String -> OvertonesO
uniqOvertonesV :: Float -> String -> OvertonesO
uniqOvertonesV Float
note String
xs =
  let ys :: [Int16]
ys = String -> String -> [Int16]
forall (t :: * -> *). Foldable t => String -> t Char -> [Int16]
uniquenessPeriodsG String
"-01" String
xs
      z :: Int16
z  = [Int16] -> Int16
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int16]
ys
      v :: [Float]
v  = (Int16 -> Float) -> [Int16] -> [Float]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int16
y -> Int16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
y Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Int16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
z) ([Int16] -> [Float]) -> [Int16] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int16]
ys
      vA :: Array Int Float
vA = (\[Float]
rs -> (Int, Int) -> [Float] -> Array Int Float
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
rs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Float]
rs) [Float]
v
      z2 :: Int
z2 = [Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
v
      v2 :: [Float]
v2 = (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
i -> Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
vA Int
i 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
0..Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] in
        ((Float, Float) -> Bool) -> OvertonesO -> OvertonesO
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (\(!Float
u,!Float
z) -> Float
u Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
notes Int
107 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
z Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.001) (OvertonesO -> OvertonesO)
-> ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> OvertonesO -> OvertonesO
forall a. Eq a => Int -> Int -> [a] -> [a]
s2L Int
1 (Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (OvertonesO -> OvertonesO)
-> ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          [Float] -> [Float] -> OvertonesO
forall a b. [a] -> [b] -> [(a, b)]
zip ((Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map (\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
1)) [Int
0..Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]) ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall a b. (a -> b) -> a -> b
$ [Float]
v2

-- | For the given frequency of the note it generates a list of the tuples, each one of which contains the harmonics' frequency and amplitude. For every given
-- first 'String' argument structure of the uniqueness (see the documentation for @ukrainian-phonetics-basic-array@ and @uniqueness-periods@ packages) it produces the unique timbre.
-- The second 'String' is used to produce the signs for harmonics coefficients.
-- Partial function.
uniqOvertonesV2 :: Float -> String -> String -> OvertonesO
uniqOvertonesV2 :: Float -> String -> String -> OvertonesO
uniqOvertonesV2 Float
note String
xs String
ts = 
  let ys :: [Int16]
ys = String -> String -> [Int16]
forall (t :: * -> *). Foldable t => String -> t Char -> [Int16]
uniquenessPeriodsG String
"-01" String
xs
      z :: Int16
z  = [Int16] -> Int16
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int16]
ys
      v :: [Float]
v  = (Int16 -> Float) -> [Int16] -> [Float]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int16
y -> Int16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
y Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Int16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
z) [Int16]
ys
      vA :: Array Int Float
vA = (\[Float]
rs -> (Int, Int) -> [Float] -> Array Int Float
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
rs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Float]
rs) [Float]
v
      z2 :: Int
z2 = Array Int Float -> Int
forall i e. Array i e -> Int
numElements Array Int Float
vA
      v2 :: [Float]
v2 = (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
i -> (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt ((Int -> Float) -> Array Int Int -> Array Int Float
forall a b i. (a -> b) -> Array i a -> Array i b
amap Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Array Int Int -> Array Int Float)
-> (String -> Array Int Int) -> String -> Array Int Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> Array Int Int
signsFromString Int
z2 (String -> Array Int Float) -> String -> Array Int Float
forall a b. (a -> b) -> a -> b
$ String
ts) Int
i) Float -> Float -> Float
forall a. Num a => a -> a -> a
* Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
vA Int
i 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
0.. Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] in
        ((Float, Float) -> Bool) -> OvertonesO -> OvertonesO
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (\(!Float
u,!Float
z) -> Float
u Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
notes Int
107 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
z Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.001) (OvertonesO -> OvertonesO)
-> ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Float, Float) -> Bool) -> OvertonesO -> OvertonesO
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Float
_, Float
t4) -> Float
t4 Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/= Float
0.0) (OvertonesO -> OvertonesO)
-> ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          Int -> Int -> OvertonesO -> OvertonesO
forall a. Eq a => Int -> Int -> [a] -> [a]
s2L Int
1 (Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (OvertonesO -> OvertonesO)
-> ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Float] -> [Float] -> OvertonesO
forall a b. [a] -> [b] -> [(a, b)]
zip ((Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map (\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
1)) [Int
0..Int
z2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]) ([Float] -> OvertonesO) -> [Float] -> OvertonesO
forall a b. (a -> b) -> a -> b
$ [Float]
v2
  
-- | For the given frequency and a Ukrainian text it generates a musical sound with the timbre obtained from the Ukrainian text (see the
-- documentation for @ukrainian-phonetics-basic-array@ package). The timbre for another given text usually differs, but can be the same. The last one is only
-- if the uniqueness structure and length are the same for both 'String'. Otherwise, they differs. This gives an opportunity to practically
-- and quickly synthesize differently sounding intervals. 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.
uniqOverSoXSynth :: Float -> String -> IO ()
uniqOverSoXSynth :: Float -> String -> IO ()
uniqOverSoXSynth Float
x String
wws = do
  let note0 :: Float
note0 = Float -> Float
closestNote Float
x
      note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
      v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
uniqOvertonesV Float
note0 String
wws
      v1 :: OvertonesO
v1    = Float -> String -> OvertonesO
uniqOvertonesV Float
note1 String
wws
  (ExitCode, String, String)
_ <- 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-.wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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 -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
note1 String
"", String
"vol",String
"0.5"] String
""
  OvertonesO -> IO ()
uniqOverSoXSynthHelp OvertonesO
v0
  OvertonesO -> IO ()
uniqOverSoXSynthHelp2 OvertonesO
v1
  IO ()
mixTest

uniqOverSoXSynthHelp1 :: String -> OvertonesO -> IO ()
uniqOverSoXSynthHelp1 :: String -> OvertonesO -> IO ()
uniqOverSoXSynthHelp1 String
xs = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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
xs String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
amplN String
""] String
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] 

uniqOverSoXSynthHelp :: OvertonesO -> IO ()
uniqOverSoXSynthHelp :: OvertonesO -> IO ()
uniqOverSoXSynthHelp = String -> OvertonesO -> IO ()
uniqOverSoXSynthHelp1 String
"test0"

uniqOverSoXSynthHelp2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelp2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelp2 = String -> OvertonesO -> IO ()
uniqOverSoXSynthHelp1 String
"test1"

-- | For the given frequency and a Ukrainian text it generates a musical sound with the timbre obtained from the Ukrainian text (see the
-- documentation for @ukrainian-phonetics-basic-array@ package). The timbre for another given text usually differs, but can be the same. The last one is only
-- if the uniqueness structure and length are the same for both 'String'. Otherwise, they differs. This gives an opportunity to practically
-- and quickly synthesize differently sounding intervals. 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 second 'String' argument is used to define signs for the harmonics coefficients for Overtones.
uniqOverSoXSynth2 :: Float -> String -> String -> IO ()
uniqOverSoXSynth2 :: Float -> String -> String -> IO ()
uniqOverSoXSynth2 Float
x String
wws 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 -> String -> OvertonesO
uniqOvertonesV2 Float
note0 String
wws String
tts
      v1 :: OvertonesO
v1    = Float -> String -> String -> OvertonesO
uniqOvertonesV2 Float
note1 String
wws String
tts
  (ExitCode, String, String)
_ <- 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-.wav", String
"synth", String
"0.5",String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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 -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
note1 String
"", String
"vol",String
"0.5"] String
""
  OvertonesO -> IO ()
uniqOverSoXSynthHelp OvertonesO
v0
  OvertonesO -> IO ()
uniqOverSoXSynthHelp2 OvertonesO
v1
  IO ()
mixTest

-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. 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 main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another 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 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.
uniqOverSoXSynthN :: Int -> Float -> Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN :: Int -> Float -> Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
ampL (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN #-}

-- | Variant of the 'uniqOverSoXSynthN4G' function where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
uniqOverSoXSynthN4GS :: Int -> Float -> Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN4GS :: Int -> Float -> Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN4GS Int
n Float
ampL Float
time3 String
zs = Int -> Float -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN4GS #-}

-- | 4G generalized variant of the 'uniqOverSoXSynthN' where you specify your own 'Durations'.
uniqOverSoXSynthN4G :: Int -> Float -> Durations -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G :: Int -> Float -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
ampL Array Int Float
v2 String
wws [Float]
vec0
 | (Float -> Bool) -> Array Int Float -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Array Int Float
v2 = String -> IO ()
putStrLn String
"Composition.Sound.Uniq.uniqOverSoXSynthN4G: You provided no valid durations data! "
 | Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0.01 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
1.0 =
    let v21 :: Array Int Float
v21 = (\[Float]
rs -> (Int, Int) -> [Float] -> Array Int Float
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,[Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
rs Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [Float]
rs) ([Float] -> Array Int Float)
-> (Array Int Float -> [Float])
-> Array Int Float
-> Array Int Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Bool) -> [Float] -> [Float]
forall a. (a -> Bool) -> [a] -> [a]
filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/= Float
0.0) ([Float] -> [Float])
-> (Array Int Float -> [Float]) -> Array Int Float -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int Float -> [Float]
forall i e. Array i e -> [e]
elems (Array Int Float -> Array Int Float)
-> Array Int Float -> Array Int Float
forall a b. (a -> b) -> a -> b
$ Array Int Float
v2
        m :: Int
m     = Array Int Float -> Int
forall i e. Array i e -> Int
numElements Array Int Float
v21
        zeroN :: Int
zeroN = [Float] -> Int
forall a. [a] -> Int
numVZeroesPre [Float]
vec0 in ((Int, Float) -> IO ()) -> [(Int, Float)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
j, Float
x) -> do
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x
              note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> OvertonesO
uniqOvertonesV Float
note0 String
wws
              v1 :: OvertonesO
v1    = Float -> String -> OvertonesO
uniqOvertonesV Float
note1 String
wws
              uniqOverSoXSynthHelpN :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0
                      then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..]
              uniqOverSoXSynthHelpN2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0
                      then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..]
              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 -> ShowS
forall a. [a] -> [a] -> [a]
++
                 Int -> ShowS
prependZeroes Int
zeroN String
"1" String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v2 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m)) String
"",String
"sine", String
"mix", Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"", String
"vol",
                    if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then String
"0.5" else String
"0"]  String
""
          (ExitCode, String, 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
          OvertonesO -> IO ()
uniqOverSoXSynthHelpN OvertonesO
v0
          OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 OvertonesO
v1
          Int -> Int -> IO ()
mixTest2 Int
zeroN Int
j) ([(Int, Float)] -> IO ())
-> ([Float] -> [(Int, Float)]) -> [Float] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Float] -> [(Int, Float)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] ([Float] -> IO ()) -> [Float] -> IO ()
forall a b. (a -> b) -> a -> b
$ [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 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 -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
0.01 Array Int Float
v2 String
wws [Float]
vec0
    else Int -> Float -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
ampL1 Array Int Float
v2 String
wws [Float]
vec0
 
-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. 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 main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another 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 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 signs of the harmonics coefficients in the generated sounds.
uniqOverSoXSynthN3 :: Int -> Float -> Float -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN3 :: Int
-> Float -> Float -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN3 Int
n Float
ampL Float
time3 String
zs = Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
ampL (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN3 #-}

-- | Variant of the 'uniqOverSoXSynthN34G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
uniqOverSoXSynthN34GS :: Int -> Float -> Float -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34GS :: Int
-> Float -> Float -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34GS Int
n Float
ampL Float
time3 String
zs = Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN34GS #-}

help14 :: Int -> Float -> Durations -> String -> String -> [Float] -> IO ()
help14 :: Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
help14 Int
n Float
ampL Array Int Float
v2 String
wws String
tts [Float]
vec0
 | Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0.01 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
1.0 = do
    let v21 :: Array Int Float
v21 = (\[Float]
rs -> (Int, Int) -> [Float] -> Array Int Float
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,[Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
rs Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [Float]
rs) ([Float] -> Array Int Float)
-> (Array Int Float -> [Float])
-> Array Int Float
-> Array Int Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Bool) -> [Float] -> [Float]
forall a. (a -> Bool) -> [a] -> [a]
filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/=Float
0.0) ([Float] -> [Float])
-> (Array Int Float -> [Float]) -> Array Int Float -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int Float -> [Float]
forall i e. Array i e -> [e]
elems (Array Int Float -> Array Int Float)
-> Array Int Float -> Array Int Float
forall a b. (a -> b) -> a -> b
$ Array Int Float
v2
        m :: Int
m     = Array Int Float -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Array Int Float
v2
        zeroN :: Int
zeroN = [Float] -> Int
forall a. [a] -> Int
numVZeroesPre [Float]
vec0 in ((Int, Float) -> IO ()) -> [(Int, Float)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
j, Float
x) -> do   
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x   
              note1 :: Float
note1 = Float -> Float
pureQuintNote Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> String -> OvertonesO
uniqOvertonesV2 Float
note0 String
wws String
tts
              v1 :: OvertonesO
v1    = Float -> String -> String -> OvertonesO
uniqOvertonesV2 Float
note1 String
wws String
tts
              uniqOverSoXSynthHelpN :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..]
              uniqOverSoXSynthHelpN2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..]
              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 -> ShowS
forall a. [a] -> [a] -> [a]
++
                Int -> ShowS
prependZeroes Int
zeroN String
"1" String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"",
                  String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int 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 -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"", String
"vol",
                    if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then String
"0.5" else String
"0"] String
""
          (ExitCode, String, 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
          OvertonesO -> IO ()
uniqOverSoXSynthHelpN OvertonesO
v0
          OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 OvertonesO
v1
          Int -> Int -> IO ()
mixTest2 Int
zeroN Int
j) ([(Int, Float)] -> IO ())
-> ([Float] -> [(Int, Float)]) -> [Float] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Float] -> [(Int, Float)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] ([Float] -> IO ()) -> [Float] -> IO ()
forall a b. (a -> b) -> a -> b
$ [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 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 -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
0.01 Array Int Float
v2 String
wws String
tts [Float]
vec0
    else Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
ampL1 Array Int Float
v2 String
wws String
tts [Float]
vec0    

-- | 4G generalized variant of the 'uniqOverSoXSynthN3' where you specify your own 'Durations'. 
uniqOverSoXSynthN34G :: Int -> Float -> Durations -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G :: Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
ampL Array Int Float
v2 String
wws String
tts [Float]
vec0
 | (Float -> Bool) -> Array Int Float -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Array Int Float
v2 = String -> IO ()
putStrLn String
"Composition.Sound.Uniq.uniqOverSoXSynthN34G: You provided no valid durations data! "
 | Bool
otherwise = Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
help14 Int
n Float
ampL Array Int Float
v2 String
wws String
tts [Float]
vec0
 
-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. 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 main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another 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 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 signs of the harmonics coefficients in the generated sounds.
-- The fourth '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.
uniqOverSoXSynthN4 :: Int -> Float -> Float -> Float -> String -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN4 :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN4 Int
n Float
ampL Float
time3 Float
dAmpl String
zs = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44G Int
n Float
ampL Float
dAmpl (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN4 #-}

-- | Variant of the 'uniqOverSoXSynthN44G' where 'Durations' are obtained from the 'String' using 'str2Durations' function. Helps to create a speech-like 
-- composition.
uniqOverSoXSynthN44GS :: Int -> Float -> Float -> Float -> String -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN44GS :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44GS Int
n Float
ampL Float
time3 Float
dAmpl String
zs = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44G Int
n Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3)
{-# INLINE uniqOverSoXSynthN44GS #-}

-- | 4G generalized variant of the 'uniqOverSoXSynthN4' where you specify your own 'Durations'. 
uniqOverSoXSynthN44G :: Int -> Float -> Float -> Durations -> String -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN44G :: Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts (String -> Array Int Int
intervalsFromString String
vs)
{-# INLINE uniqOverSoXSynthN44G #-}

help15 :: Int -> Float -> Float -> Durations -> String -> String -> Intervals -> [Float] -> IO ()
help15 :: Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
help15 Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0 = do
  let v21 :: Array Int Float
v21 = (\[Float]
rs -> (Int, Int) -> [Float] -> Array Int Float
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,[Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
rs Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [Float]
rs)([Float] -> Array Int Float)
-> (Array Int Float -> [Float])
-> Array Int Float
-> Array Int Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Float -> Bool) -> [Float] -> [Float]
forall a. (a -> Bool) -> [a] -> [a]
filter (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
/=Float
0.0) ([Float] -> [Float])
-> (Array Int Float -> [Float]) -> Array Int Float -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int Float -> [Float]
forall i e. Array i e -> [e]
elems (Array Int Float -> Array Int Float)
-> Array Int Float -> Array Int Float
forall a b. (a -> b) -> a -> b
$ Array Int Float
v2
      m :: Int
m     = Array Int Float -> Int
forall i e. Array i e -> Int
numElements Array Int Float
v2
      zeroN :: Int
zeroN = [Float] -> Int
forall a. [a] -> Int
numVZeroesPre [Float]
vec0
      l :: Int
l     = Array Int Int -> Int
forall i e. Array i e -> Int
numElements Array Int Int
v3 in ((Int, Float) -> IO ()) -> [(Int, Float)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
j, Float
x) -> do   
          let note0 :: Float
note0 = Float -> Float
closestNote Float
x
              note1 :: Maybe Float
note1 = Int -> Float -> Maybe Float
dNote (Array Int Int -> Int -> Int
forall i e. Array i e -> Int -> e
unsafeAt Array Int Int
v3 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
l)) Float
note0
              v0 :: OvertonesO
v0    = Float -> String -> String -> OvertonesO
uniqOvertonesV2 Float
note0 String
wws String
tts
              v1 :: OvertonesO
v1    = if Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
note1 then []
                      else Float -> String -> String -> OvertonesO
uniqOvertonesV2 (Maybe Float -> Float
forall a. HasCallStack => Maybe a -> a
fromJust Maybe Float
note1) String
wws String
tts
              uniqOverSoXSynthHelpN :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                  String
"sine",Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..]
              uniqOverSoXSynthHelpN2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 = ((Integer, (Float, Float)) -> IO (ExitCode, String, String))
-> [(Integer, (Float, Float))] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Integer
i, (Float
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 -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Integer -> String
forall a. Show a => a -> String
show (Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
2)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",
                   String
"sine", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
noteN String
"", String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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
"") ([(Integer, (Float, Float))] -> IO ())
-> (OvertonesO -> [(Integer, (Float, Float))])
-> OvertonesO
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Integer] -> OvertonesO -> [(Integer, (Float, Float))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] 
              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 -> ShowS
forall a. [a] -> [a] -> [a]
++
                 Int -> ShowS
prependZeroes Int
zeroN String
"1" String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note01 String
"",
                   String
"vol",if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 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 -> ShowS
forall a. [a] -> [a] -> [a]
++
                 Int -> ShowS
prependZeroes Int
zeroN String
"1" String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
".wav", String
"synth", Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) (Float -> Float
forall a. Num a => a -> a
abs (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m))) String
"",String
"sine", Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) a
note02 String
"",
                    String
"vol", if Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v21 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
m) Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
> Float
0.0 then Maybe Int -> Float -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
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 { (ExitCode, String, String)
_ <- Float -> IO (ExitCode, String, String)
forall a. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                                     ; OvertonesO -> IO ()
uniqOverSoXSynthHelpN OvertonesO
v0 }
          else do { (ExitCode, String, String)
_ <- Float -> IO (ExitCode, String, String)
forall a. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain0 Float
note0
                  ; (ExitCode, String, String)
_ <- Float -> IO (ExitCode, String, String)
forall a. RealFloat a => a -> IO (ExitCode, String, String)
soxSynthHelpMain1 (Maybe Float -> Float
forall a. HasCallStack => Maybe a -> a
fromJust Maybe Float
note1)
                  ; OvertonesO -> IO ()
uniqOverSoXSynthHelpN OvertonesO
v0
                  ; OvertonesO -> IO ()
uniqOverSoXSynthHelpN2 OvertonesO
v1}
          Int -> Int -> IO ()
mixTest2 Int
zeroN Int
j) ([(Int, Float)] -> IO ())
-> ([Float] -> [(Int, Float)]) -> [Float] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Float] -> [(Int, Float)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] ([Float] -> IO ()) -> [Float] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Float]
vec0
 
-- | 5G generalized variant of the 'uniqOverSoXSynthN44G' where you specify your own 'Intervals'. 
uniqOverSoXSynthN45G :: Int -> Float -> Float -> Durations -> String -> String -> Intervals -> [Float] -> IO ()
uniqOverSoXSynthN45G :: Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0
 | (Float -> Bool) -> Array Int Float -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Array Int Float
v2 = String -> IO ()
putStrLn String
"Composition.Sound.Uniq.uniqOverSoXSynthN45G: You provided no valid durations data! "
 | Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0.01 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
1.0 = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
help15 Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [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 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
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
0.01 Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0
    else Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL1 Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0    

-- | 6G generalized variant of the 'uniqOverSoXSynthN45G' where you specify your own 'Strengths' and a limit (as the last 'Float') when less volume level 
-- sound files are treated as a silent ones and are not adjusted. 
uniqOverSoXSynthN46G :: Int -> Float -> Float -> Durations -> String -> String -> Intervals -> [Float] -> Strengths -> Float -> IO ()
uniqOverSoXSynthN46G :: Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthN46G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0 Array Int Float
v6 Float
limV
 | (Float -> Bool) -> Array Int Float -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0.0) Array Int Float
v2 = String -> IO ()
putStrLn String
"Composition.Sound.Uniq.uniqOverSoXSynthN46G: You provided no valid durations data! "
 | Array Int Float -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
F.null Array Int Float
v6 = String -> IO ()
putStrLn String
"Composition.Sound.Uniq.uniqOverSoXSynthN46G: You did not provide a volume adjustments vector! "
 | Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
>= Float
0.01 Bool -> Bool -> Bool
&& Float -> Float
forall a. Num a => a -> a
abs Float
ampL Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
<= Float
1.0 = do
     let zeroN :: Int
zeroN = [Float] -> Int
forall a. [a] -> Int
numVZeroesPre [Float]
vec0
         l6 :: Int
l6 = Array Int Float -> Int
forall i e. Array i e -> Int
numElements Array Int Float
v6
     Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
help15 Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0
     ((Int, Float) -> IO ()) -> [(Int, Float)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
j, Float
_) -> String -> Float -> Float -> IO ()
apply6GSilentFile (String
"result" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
prependZeroes Int
zeroN (Int -> String
forall a. Show a => a -> String
show Int
j) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".wav") Float
limV (Array Int Float -> Int -> Float
forall i e. Array i e -> Int -> e
unsafeAt Array Int Float
v6 (Int
j Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
l6))) ([(Int, Float)] -> IO ())
-> ([Float] -> [(Int, Float)]) -> [Float] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Float] -> [(Int, Float)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] ([Float] -> IO ()) -> [Float] -> IO ()
forall a b. (a -> b) -> a -> b
$ [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 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
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthN46G Int
n Float
0.01 Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0 Array Int Float
v6 Float
limV
    else Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthN46G Int
n Float
ampL1 Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vec0 Array Int Float
v6 Float
limV

-- | Variant of the 'uniqOverSoXSynthN45G' where 'Intervals' are obtained from the 'String' using 'intervalsFromStringG' function. Helps to create a speech-like 
-- composition.
uniqOverSoXSynthN45GS :: Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> [Float] -> IO ()
uniqOverSoXSynthN45GS :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Array Int Int
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN45GS Int
n Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts Array Int Int
v3 String
vs = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v3 String
vs)
{-# INLINE uniqOverSoXSynthN45GS #-}

-- | Variant of the 'uniqOverSoXSynthN46G' where 'Strengths' are obtained from the 'String' using 'str2Volume' function. Helps to create a speech-like 
-- composition.
uniqOverSoXSynthN46GS :: Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> [Float] -> String ->
  Float -> IO ()
uniqOverSoXSynthN46GS :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Array Int Int
-> String
-> [Float]
-> String
-> Float
-> IO ()
uniqOverSoXSynthN46GS Int
n Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts Array Int Int
v3 String
vs [Float]
vec0 String
xxs Float
limV = Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthN46G Int
n Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts 
  (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v3 String
vs) [Float]
vec0 (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthN46GS #-}

-- | A variant of 'uniqOverSoXSynthN46GS' where 'Strengths' and 'Durations' are obtained from the same Ukrainian text specified as 
-- the last 'String' argument. The second '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@.
uniqOverSoXSynthN46GSu :: Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> [Float] -> String -> Float -> IO ()
uniqOverSoXSynthN46GSu :: Int
-> Float
-> Float
-> Float
-> String
-> String
-> Array Int Int
-> String
-> [Float]
-> String
-> Float
-> IO ()
uniqOverSoXSynthN46GSu Int
n Float
ampL Float
time3 Float
dAmpl String
wws String
tts Array Int Int
v5 String
vs [Float]
vec0 String
xxs Float
limV = 
 Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthN46G Int
n Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
xxs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v5 String
vs) [Float]
vec0 (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthN46GSu #-} 

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'Array' 'Int' 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 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*\" 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.
uniqOverSoXSynthNGen :: FilePath -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGen :: String -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGen String
file Int
m = String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE String
file Int
m Int
12
{-# INLINE uniqOverSoXSynthNGen #-}

-- | Similar to 'uniqOverSoXSynthNGen', 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 'uniqOverSoXSynthNGen'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9. 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@.
uniqOverSoXSynthNGenE :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE :: String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
wws = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> IO ()
unGenNE4Gi Int
n String
file Int
m Int
ku Float
ampL (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3) String
wws

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

-- | Variant of the 'uniqOverSoXSynthNGenE4G' 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@.
uniqOverSoXSynthNGenE4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GS :: String -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GS String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
wws = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> IO ()
unGenNE4Gi Int
n String
file Int
m Int
ku Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws
  
-- | Generalized version of the 'uniqOverSoXSynthNGenE4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGenE4GSPar :: FilePath -> Params -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GSPar :: String -> Params -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GSPar String
file Params
params Float
ampL Float
time3 String
zs String
wws = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String -> Params -> Float -> Array Int Float -> String -> IO ()
unGenNE4GiPar Int
n String
file Params
params Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws  

-- | 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@.
unGenNE4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
unGenNE4Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> IO ()
unGenNE4Gi Int
n String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Int -> Int -> [Float] -> [Float]
liftInEnkuV Int
m Int
ku ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> ([Int] -> [Int]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int -> Float -> Array Int Float -> String -> [Float] -> IO ()
uniqOverSoXSynthN4G Int
n Float
ampL Array Int Float
v2 String
wws [Float]
vecB
  IO ()
endFromResult

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

-- | 4G genaralized version of the 'uniqOverSoXSynthNGenE' 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@.
uniqOverSoXSynthNGenE4G :: FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
uniqOverSoXSynthNGenE4G :: String -> Int -> Int -> Float -> Array Int Float -> String -> IO ()
uniqOverSoXSynthNGenE4G String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> IO ()
unGenNE4Gi Int
n String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws

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

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'Array' 'Int' 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 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*\" 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 third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
uniqOverSoXSynthNGen3 :: FilePath -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3 :: String
-> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3 String
file Int
m = String
-> Int
-> Int
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen3E String
file Int
m Int
12
{-# INLINE uniqOverSoXSynthNGen3 #-}

-- | Similar to 'uniqOverSoXSynthNGen3', 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 'uniqOverSoXSynthNGen3'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9. 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@.
uniqOverSoXSynthNGen3E :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E :: String
-> Int
-> Int
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen3E String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
wws String
tts = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4Gi Int
n String
file Int
m Int
ku Float
ampL (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3) String
wws String
tts

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

-- | Variant of the 'uniqOverSoXSynthNGen3E4G' 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@.
uniqOverSoXSynthNGen3E4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GS :: String
-> Int
-> Int
-> Float
-> Float
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen3E4GS String
file Int
m Int
ku Float
ampL Float
time3 String
zs String
wws String
tts = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4Gi Int
n String
file Int
m Int
ku Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts

-- | Generalized version of the 'uniqOverSoXSynthNGen3E4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGen3E4GSPar :: FilePath -> Params -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GSPar :: String
-> Params -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GSPar String
file Params
params Float
ampL Float
time3 String
zs String
wws String
tts = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Params
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4GiPar Int
n String
file Params
params Float
ampL (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
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@.
unGenN3E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> String -> String -> IO ()
unGenN3E4Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4Gi Int
n String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws String
tts = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Int -> Int -> [Float] -> [Float]
liftInEnkuV Int
m Int
ku ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> ([Int] -> [Int]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int
-> Float -> Array Int Float -> String -> String -> [Float] -> IO ()
uniqOverSoXSynthN34G Int
n Float
ampL Array Int Float
v2 String
wws String
tts [Float]
vecB
  IO ()
endFromResult

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

-- | 4G genaralized version of the 'uniqOverSoXSynthNGen3E' 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@.
uniqOverSoXSynthNGen3E4G :: FilePath -> Int -> Int -> Float -> Durations -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4G :: String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen3E4G String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws String
tts = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4Gi Int
n String
file Int
m Int
ku Float
ampL Array Int Float
v2 String
wws String
tts
   
-- | Generalized version of the 'uniqOverSoXSynthNGen3E4G' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGen3E4GPar :: FilePath -> Params -> Float -> Durations -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GPar :: String
-> Params -> Float -> Array Int Float -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GPar String
file Params
params Float
ampL Array Int Float
v2 String
wws String
tts = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Params
-> Float
-> Array Int Float
-> String
-> String
-> IO ()
unGenN3E4GiPar Int
n String
file Params
params Float
ampL Array Int Float
v2 String
wws String
tts   

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'Array' 'Int' 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 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*\" 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 third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
-- The fourth '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 an experimental feature.
uniqOverSoXSynthNGen4 :: FilePath -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4 :: String
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4 String
file Int
m = String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4E String
file Int
m Int
12
{-# INLINE uniqOverSoXSynthNGen4 #-}

-- | Similar to 'uniqOverSoXSynthNGen4', 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 'uniqOverSoXSynthNGen4'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9. 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@.
uniqOverSoXSynthNGen4E :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4E String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts String
vs = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl (Int -> String -> Float -> Array Int Float
str2DurationsDef Int
n String
zs Float
time3) String
wws String
tts String
vs

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

-- | Variant of the 'uniqOverSoXSynthNGen4E4G' 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@.
uniqOverSoXSynthNGen4E4GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4GS :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4E4GS String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts String
vs = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts String
vs

-- | Generalized version of the 'uniqOverSoXSynthNGen4E4GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGen4E4GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4GSPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4E4GSPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts String
vs = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Params
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4GiPar Int
n String
file Params
params Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts String
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@.
unGenN4E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> String -> IO ()
unGenN4E4Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Int -> Int -> [Float] -> [Float]
liftInEnkuV Int
m Int
ku ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> ([Int] -> [Int]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs [Float]
vecB
  IO ()
endFromResult

-- | Generalized version of the 'unGenN4E4Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
unGenN4E4GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> String -> String -> IO ()
unGenN4E4GiPar :: Int
-> String
-> Params
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4GiPar Int
n String
file Params
params Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Params -> [Float] -> [Float]
liftInParamsV Params
params ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> [Float]
-> IO ()
uniqOverSoXSynthN44G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs [Float]
vecB
  IO ()
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@.
unGenN4E5Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
unGenN4E5Gi :: Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
unGenN4E5Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Int -> Int -> [Float] -> [Float]
liftInEnkuV Int
m Int
ku ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> ([Int] -> [Int]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int
11440::Int)) ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vecB
  IO ()
endFromResult

-- | Generalized version of the 'unGenN4E5Gi' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
unGenN4E5GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
unGenN4E5GiPar :: Int
-> String
-> Params
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
unGenN4E5GiPar Int
n String
file Params
params Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 = do
  [Int]
vecA <- String -> Int -> IO [Int]
freqsFromFile String
file Int
n
  let vecB :: [Float]
vecB = Params -> [Float] -> [Float]
liftInParamsV Params
params ([Float] -> [Float]) -> ([Int] -> [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Float) -> [Int] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$ [Int]
vecA
  Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> [Float]
-> IO ()
uniqOverSoXSynthN45G Int
n Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 [Float]
vecB
  IO ()
endFromResult  
  
-- | 4G genaralized version of the 'uniqOverSoXSynthNGen4E' 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@.
uniqOverSoXSynthNGen4E4G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4G :: String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
uniqOverSoXSynthNGen4E4G String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> String
-> IO ()
unGenN4E4Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts String
vs

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

-- | 5G genaralized version of the 'uniqOverSoXSynthNGen4E' where you provide your own 'Durations' and '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@.
uniqOverSoXSynthNGen4E5G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
uniqOverSoXSynthNGen4E5G :: String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
uniqOverSoXSynthNGen4E5G String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
unGenN4E5Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3

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

-- | Variant of the 'uniqOverSoXSynthNGen4E5G' where 'Intervals' are obtained from the 'String' using 'intervalsFromStringG' 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@.
uniqOverSoXSynthNGen4E5GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> IO ()
uniqOverSoXSynthNGen4E5GS :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Array Int Int
-> String
-> IO ()
uniqOverSoXSynthNGen4E5GS String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts Array Int Int
v3 String
vs = do
  Int
n <- String -> IO Int
duration1000 String
file
  Int
-> String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
unGenN4E5Gi Int
n String
file Int
m Int
ku Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v3 String
vs)

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

-- | 6G generalized function for 'uniqOverSoXSynthNGen4E5G' 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@.
uniqOverSoXSynthNGen4E6G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> Strengths -> Float -> IO ()
uniqOverSoXSynthNGen4E6G :: String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6G String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 Array Int Float
v6 Float
limV = 
 String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> IO ()
uniqOverSoXSynthNGen4E5G String
file Int
m Int
ku Float
ampL Float
dAmpl Array Int Float
v2 String
wws String
tts Array Int Int
v3 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Array Int Float -> String -> String -> Float -> IO ()
apply6G2 Array Int Float
v6 String
"221w" String
"result" Float
limV IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
endFromResult

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

-- | A variant of 'uniqOverSoXSynthNGen4E6G' 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@.
uniqOverSoXSynthNGen4E6GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> 
  String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GS :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Array Int Int
-> String
-> String
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GS String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts Array Int Int
v5 String
vs String
xxs Float
limV = 
 String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6G String
file Int
m Int
ku Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v5 String
vs) (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthNGen4E6GS #-} 

-- | Generalized version of the 'uniqOverSoXSynthNGen4E6GS' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGen4E6GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> 
  String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> String
-> Array Int Int
-> String
-> String
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GSPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
zs String
wws String
tts Array Int Int
v5 String
vs String
xxs Float
limV = 
 String
-> Params
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GPar String
file Params
params Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
zs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v5 String
vs) (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthNGen4E6GSPar #-}
 
-- | A variant of 'uniqOverSoXSynthNGen4E6GS' where 'Strengths' and 'Durations' are obtained from the same Ukrainian text specified as 
-- the last 'String' argument. The second '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@.
uniqOverSoXSynthNGen4E6GSu :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSu :: String
-> Int
-> Int
-> Float
-> Float
-> Float
-> String
-> String
-> Array Int Int
-> String
-> String
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GSu String
file Int
m Int
ku Float
ampL Float
time3 Float
dAmpl String
wws String
tts Array Int Int
v5 String
vs String
xxs Float
limV = 
 String
-> Int
-> Int
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6G String
file Int
m Int
ku Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
xxs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v5 String
vs) (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthNGen4E6GSu #-} 
 
-- | Generalized version of the 'uniqOverSoXSynthNGen4E6GSu' where instead of lifting with 'liftInEnkuV' 'liftInParamsV' is used. It allows e. g. to 
-- use some tonality. For more information, please, refer to 'filterInParams'.
uniqOverSoXSynthNGen4E6GSuPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> Intervals -> String -> String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSuPar :: String
-> Params
-> Float
-> Float
-> Float
-> String
-> String
-> Array Int Int
-> String
-> String
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GSuPar String
file Params
params Float
ampL Float
time3 Float
dAmpl String
wws String
tts Array Int Int
v5 String
vs String
xxs Float
limV = 
 String
-> Params
-> Float
-> Float
-> Array Int Float
-> String
-> String
-> Array Int Int
-> Array Int Float
-> Float
-> IO ()
uniqOverSoXSynthNGen4E6GPar String
file Params
params Float
ampL Float
dAmpl (String -> Float -> Array Int Float
str2Durations String
xxs Float
time3) String
wws String
tts (Array Int Int -> String -> Array Int Int
intervalsFromStringG Array Int Int
v5 String
vs) (String -> Array Int Float
str2Volume String
xxs) Float
limV
{-# INLINE uniqOverSoXSynthNGen4E6GSuPar #-}