dobutokO2-0.36.3.0: Helps to create experimental music from a file (or its part) and a Ukrainian text.

Copyright(c) OleksandrZhabenko 2020
LicenseMIT
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

DobutokO.Sound.Functional

Contents

Description

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.

Synopsis

Type synonyms with different semantics

type SoundsO = Vector (Double, Double) Source #

Is used to represent a sequence of intervals, each note being a Double value (its frequency in Hz).

type OvertonesO = Vector (Double, Double) Source #

Is used to represent a set of overtones for the single sound, the first Double value is a frequency and the second one -- an amplitude.

type NotePairs = Vector (Double, Double) Source #

Is used to represent a set of pairs of notes for each element of which the Double values (notes frequencies in Hz) are somewhat musically connected one with another..

type Durations = Vector Double Source #

Is used to represent a set of durations parameters of the sounds and pauses. The positive value corresponds to the sound and the negative one -- to the pause.

type Strengths = Vector Double Source #

Is used to represent a set of volumes in the amplitude scale for SoX "vol" effect.

type StrengthsDb = Vector Double Source #

Is used to represent a set of volumes in the dB scale for SoX "vol" effect.

type Intervals = Vector Int Source #

Is used to represent a set of intervals for notes (each element is a number of semi-tones between parts of interval). Positive values corresponds to lower notes and negative to higher ones.

Work with notes (general)

notes :: Vector Double Source #

Vector of musical notes in Hz.

neighbourNotes :: Double -> Vector Double -> (Double, Double) Source #

Function returns either the nearest two musical notes if frequency is higher than one for C0 and lower than one for B8 or the nearest note duplicated in a tuple.

closestNote :: Double -> Double Source #

Returns the closest note to the given frequency in Hz.

pureQuintNote :: Double -> Double Source #

Returns a pure quint lower than the given note.

overTones :: Double -> OvertonesO Source #

For the given frequency of the note it generates a Vector of the tuples, each one of which contains the harmonics' frequency and amplitude.

Work with enky (extension to octaves functionality)

nkyT :: Int -> NotePairs Source #

Returns a Vector of tuples with the lowest and highest frequencies for the notes in the sets consisting of n consequential notes (including semi-tones). An Int parameter defines this n. It can be 2, 3, 4, 6, 9, or 12 (the last one is for default octaves, see octavesT). So for different valid n you obtain doubles, triples and so on. The function being applied returns a Vector of such sets with their respective lowest and highest frequencies.

whichEnka :: Int -> Double -> Maybe Int Source #

Similarly to whichOctave returns a Maybe number (actually frequency) for the n-th elements set of notes (see nkyT). An Int parameter defines that n.

enkuUp :: Int -> Double -> Double Source #

Returns an analogous note in the higher n-th elements set (its frequency in Hz) (see nkyT). An Int parameter defines this n.

enkuDown :: Int -> Double -> Double Source #

Returns an analogous note in the lower n-th elements set (its frequency in Hz) (see nkyT). An Int parameter defines this n.

liftInEnkuV :: Int -> Int -> Vector Double -> Vector Double Source #

Similarly to liftInOctaveV returns a Vector Double (actually frequencies) for the n-th elements set of notes (see nkyT) instead of octaves. A second Int parameter defines that n.

liftInEnku :: Int -> Int -> Double -> Maybe Double Source #

Similarly to liftInOctave returns a Maybe number (actually frequency) for the n-th elements set of notes (see nkyT). A second Int parameter defines that n. Not all pairs return Just x.

Work with octaves

octavesT :: NotePairs Source #

Returns a Vector of tuples with the lowest and highest frequencies for the notes in the octaves.

Combining intermediate files

mixTest :: IO () Source #

Combines (mixes) all "test*" files in the given directory. The files should be similar in parameters and must be sound files for SoX to work on them properly. Afterwards, the function deletes these combined files.

mixTest2 :: Int -> Int -> IO () Source #

Combines (mixes) all "test*" files in the given directory. The files should be similar in parameters and must be sound files for SoX to work on them properly. Afterwards, the function deletes these combined files. The name of the resulting file depends on the first two command line arguments so that it is easy to produce unique names for the consequent call for the function.

Working with files

freqsFromFile :: FilePath -> Int -> IO (Vector Int) Source #

Gets Vector of Int frequencies from the given FilePath using SoX. The frequencies are "rough" according to the SoX documentation and the duration is too small so they can be definitely other than expected ones. Is used as a source of variable numbers (somewhat close each to another in their order but not neccessarily). .

endFromResult :: IO () Source #

Gets an "end.wav" file from the intermediate "result*.wav" files in the current directory. If it is not successful, produces the notification message and exits without error. If you would like to create the file if there are too many intermediate ones, please, run "dobutokO2 8" or "dobutokO2 80" in the current directory.

Work with overtones

overSoXSynth :: Double -> IO () Source #

For the given frequency it generates a musical sound with a timbre. The main component of the sound includes the lower pure quint, which can be in the same octave or in the one with the number lower by one. Please, check before executing whether there is no "x.wav", "test*", "result*" and "end.wav" files in the current directory, because they can be overwritten.

Use additional function as a parameter

overSoXSynth2FDN :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO () Source #

Similar to overSoXSynth2DN but instead of overTones function, it uses volatile function f::Double -> Vector (Double, Double) with somewhat sophisticated mechanism to normalize the resulting Vector elements (Double, Double). The last one is an experimental feature, so it is your responsibility to provide a function so that it does not lead to clipping. In such a case, the result of application of the convertToProperUkrainian to the String parameter must not be empty. Int argument is an index of the element to be taken from the intervalsFromString applied to the String argument. To obtain compatible with versions prior to 0.20.0.0 behaviour, use for the Int 0.

Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function. But for a lot of functions this works well.

It is recommended to fully simplify the computation for "f" function before using it in the overSoXSynth2FDN.

overSoXSynth2FDN_B :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> IO () Source #

Similar to overSoXSynth2DN but instead of overTones function, it uses volatile function f::Double -> Vector (Double, Double) with somewhat sophisticated mechanism to normalize the resulting Vector elements (Double, Double). The last one is experimental feature, so it is your responsibility to provide a function so that it does not lead to clipping. In such a case, the result of application of the convertToProperUkrainian to the String parameter must not be empty. The function also tries to perform filtering to avoid possible beating. The third Double parameter in the tuple is used as a limit for frequencies difference in Hz to be filtered out from the resulting sound. It is considered to be from the range [0.1..10.0]. An Int parameter is used to define the needed interval. To obtain compatible with versions prior to 0.20.0.0 behaviour, use for the Int 0.

Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function. But for a lot of functions this works well.

It is recommended to fully simplify the computation for "f" function before using it in the overSoXSynth2FDN_B.

Just simple function application

overSoXSynth2FDN_S :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO () Source #

Similar to overSoXSynth2FDN but it does not make any normalizing transformations with the Vector argument. To be used properly, it is needed that every second element in the tuple in the Vector argument must be in the range [-1.0..1.0] and every first element must be in between 16.351597831287414 and 7902.132820097988 (Hz). An Int parameter is used to define an interval. To obtain compatible with versions prior to 0.20.0.0 behaviour, use for the Int 0.

Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function. But for a lot of functions this works well.

It is recommended to fully simplify the computation for "f" function before using it in the overSoXSynth2FDN_S.

With additional filtering

overSoXSynth2FDN_Sf :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO () Source #

Similar to overSoXSynth2FDN_S but additionally the program filters out from the resulting Vector after "f" application values that are smaller by absolute value than 0.001. An Int parameter is used to define an interval. To obtain compatible with versions prior to 0.20.0.0 behaviour, use for the Int 0.

Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function. But for a lot of functions this works well.

It is recommended to fully simplify the computation for "f" function before using it in the overSoXSynth2FDN_Sf.

overSoXSynth2FDN_Sf3 :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> IO () Source #

Similar to overSoXSynth2FDN_S but additionally the program filters out from the resulting Vector after "f" application values that are smaller than the third Double parameter by an absolute value in the triple of Double's. An Int parameter is used to define an interval. To obtain compatible with versions prior to 0.20.0.0 behaviour, use for the Int 0.

Be aware that the result can be rather unpredictable (the program can even obtain segmentation fault) for not very suitable function. But for a lot of functions this works well.

It is recommended to fully simplify the computation for "f" function before using it in the overSoXSynth2FDN_Sf3.

Use additional function and Ukrainian texts and generates melody

overSoXSynthGen2FDN :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> IO () Source #

Uses additional Int parameters. The first one is a number of enka (see nkyT). The second one defines, to which n-th elements set (see nkyT) belongs the obtained higher notes in the intervals. To obtain reasonable results, please, use for the first one 2, 3, 4, 6, 9, or 12. The first String parameter is used to produce durations of the notes. The second one is used to define intervals. A Double parameter is a basic sound duration, it defines tempo of the melody in general.

overSoXSynthGen2FDN_B :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> Double -> String -> String -> IO () Source #

Uses additional Int parameters. The first one is a number of enka (see nkyT). The second one defines, to which n-th elements set (see nkyT) belongs the obtained higher notes in the intervals. To obtain reasonable results, please, use for the first one 2, 3, 4, 6, 9, or 12. The first String parameter is used to produce durations of the notes. The second one is used to define intervals. The first Double parameter is a basic sound duration, it defines tempo of the melody in general. The second one is a limit for frequencies difference in Hz to be filtered out from the resulting sound. It is considered to be from the range [0.1..10.0].

overSoXSynthGen2FDN_S :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> IO () Source #

Similar to overSoXSynthGen2FDN, but instead of overSoXSynth2FDN uses overSoXSynth2FDN_S function.

overSoXSynthGen2FDN_Sf :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> IO () Source #

Similar to overSoXSynthGen2FDN_S, but instead of overSoXSynth2FDN_S uses overSoXSynth2FDN_Sf function. 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.

dNote :: Int -> Double -> Maybe Double Source #

Function to get from the number of semi-tones and a note a Maybe note for the second lower note in the interval if any. If there is no need to obtain such a note, then the result is Nothing.

1G generalized functions with dB volume overtones adjustments

overSoXSynth2FDN1G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> IO () Source #

Vector of Double is a vector of dB volume adjustments for the corresponding harmonices (overtones).

overSoXSynth2FDN_B1G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> Vector Double -> IO () Source #

Vector of Double is a vector of dB volume adjustments for the corresponding harmonices (overtones).

overSoXSynth2FDN_S1G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> IO () Source #

Generalized version of the overSoXSynth2FDN_S with the additional volume adjustment in dB for overtones given by Vector of Double.

overSoXSynth2FDN_Sf1G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf with a possibility to adjust volume using adjust_dbVol. Vector of Double is used to specify adjustments in dB. For more information, please, refer to adjust_dbVol.

overSoXSynth2FDN_Sf31G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> Vector Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf3 function with a possibility to adjust volume using adjust_dBVol. Vector of Double specifies the needed adjustments in dB.

partialTest_k1G :: OvertonesO -> Int -> String -> Vector Double -> IO () Source #

Generalized version of the partialTest_k with the additional volume adjustment in dB given by Vector of Double.

2G generalized functions with additional sound quality specifying

overSoXSynth2FDN2G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> String -> IO () Source #

Similar to overSoXSynth2FDN1G, but additionally allows to specify by the second String argument a quality changes to the generated files (please, see soxBasicParams). Since version 0.36.0.0 the function supports generation of the pauses.

overSoXSynth2FDN_B2G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> Vector Double -> String -> IO () Source #

Generalized version of the overSoXSynth2FDN_B1G with a possibility to specify sound quality parameters using additional second String argument. For more information, please, refer to soxBasicParams.

overSoXSynth2FDN_S2G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> String -> IO () Source #

Generalized version of the overSoXSynth2FDN_S1G with a possibility to specify sound quality parameters using the second String argument. For more information, please, refer to soxBasicParams.

overSoXSynth2FDN_Sf2G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> String -> Vector Double -> String -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf1G with a possibility to specify sound quality using the second String argument. For more information, please, refer to soxBasicParams.

overSoXSynth2FDN_Sf32G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> Vector Double -> String -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf31G with a possibility to specify sound quality using the second String parameter. For more information, please, refer to soxBasicParams.

partialTest_k2G :: OvertonesO -> Int -> String -> Vector Double -> String -> IO () Source #

Generalized version of the partialTest_k1G with a possibility to change sound quality parameters using the additional second String argument. For more information, please, refer to soxBasicParams.

soundGenF32G :: Vector (Double -> Double) -> Vector Double -> Vector Int -> (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Vector Double -> String -> IO () Source #

Generalized variant of the soundGenF31G with a possibility to specify sound quality using the String argument. For more information, please, refer to soxBasicParams.

2G generalized functions for melody producing

overSoXSynthGen2FDN_SG2G :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> String -> IO ()) -> String -> IO () Source #

Generalized variant of the overSoXSynthGen2FDN_SG with a possibility to specify with the third String argument sound quality parameters. Besides, the second from the end argument (a function) needs to be one more argument -- just also String. For more information, please, refer to soxBasicParams. 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.

overSoXSynthGen2FDN_Sf3G2G :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> String -> IO ()) -> String -> IO () Source #

Generalized variant of the ovorSoXSynthGen2FDN_Sf3G with a possibility to specify sound quality with the third String argument. Besides, the second from the end argument (a function) needs to be one more argument -- just also String. For more information, please, refer to soxBasicParams. 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.

2G generalized auxiliary functions

mixTest2G :: String -> IO () Source #

Similar to mixTest, but allows to change the sound quality parameters for the resulting file. For more information, please, refer to soxBasicParams.

mixTest22G :: Int -> Int -> String -> IO () Source #

Similar to mixTest, but allows to change the sound quality parameters for the resulting file. For more information, please, refer to soxBasicParams. The name of the resulting file depends on the first two command line arguments so that it is easy to produce unique names for the consequent call for the function.

endFromResult2G :: String -> IO () Source #

Similar to endFromResult, but uses additional String argument to change sound quality parameters. For more information, please, refer to soxBasicParams.

Generalized functions with several functional parameters

soundGenF3 :: Vector (Double -> Double) -> Vector Double -> Vector Int -> (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> IO () Source #

Can generate multiple notes with their respective overtones that are played simultaneously (e. g. it can be just one note with overtones, an interval with overtones, an accord with overtones etc.). This allows to get a rather complex or even complicated behaviour to obtain expressive and rich sound.

overSoXSynthGen2FDN_SG :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO ()) -> IO () Source #

Similar to overSoXSynthGen2FDN, but instead of overSoXSynth2FDN uses overSoXSynth2FDN_S function. Note that the first 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.

overSoXSynthGen2FDN_Sf3G :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double, Double) -> Int -> String -> IO ()) -> IO () Source #

Similar to overSoXSynthGen2FDN_S, but instead of overSoXSynth2FDN_S uses overSoXSynth2FDN_Sf3 function. 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.

1G generalized function with db volume overtones adjustments and several functional parameters

soundGenF31G :: Vector (Double -> Double) -> Vector Double -> Vector Int -> (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Vector Double -> IO () Source #

Generalized variant of the soundGenF3 with volume adjustment in dB given by the second Vector Double for the overtones.

Auxiliary functions

adjust_dbVol :: [String] -> Double -> [String] Source #

Is used internally in the readProcessWithExitCode to adjust volume for the sound with additional dB value given by Double argument.

partialTest_k :: OvertonesO -> Int -> String -> IO () Source #

Creates part of the needed "test*.wav" files in the current directory.

prependZeroes :: Int -> String -> String Source #

Additional function to prepend zeroes to the given String. The number of them are just that one to fulfill the length to the given Int parameter.

numVZeroesPre :: Vector a -> Int Source #

Is a minimal number of decimal places that are just enough to represent a length of the Vector given. For an empty returns 0.

syllableStr :: Int -> String -> [Int] Source #

Function is used to generate a rhythm of the resulting file 'end.wav' from the Ukrainian text and a number of sounds either in the syllables or in the words without vowels.

doubleVecFromVecOfDouble :: (Double -> OvertonesO) -> Double -> Vector (Maybe Double) -> Vector OvertonesO Source #

Generates a Vector of OvertonesO that represents the sound.

Working with Intervals

intervalsFromString :: String -> Intervals Source #

Function is used to get numbers of intervals from a Ukrainian String. It is used internally in the uniqOverSoXSynthN4 function.

vStrToVInt :: Vector String -> Intervals Source #

The default way to get Intervals from a converted Ukrainian text.

strToInt :: String -> Int Source #

The default way to get number of semi-tones between notes in a single element of Intervals.

Working with OvertonesO and function f

maybeFFromStrVec :: Int -> Double -> String -> Maybe (Double, Double -> Vector (Double, Double)) Source #

Gets a function f::Double -> OvertonesO that can be used further. Has two variants with usage of closestNote (Int argument is greater than 0)v and without it (Int argument is less than 0). For both cases String must be in a form list of tuples of pairs of Double to get somewhat reasonable result. The function f can be shown using a special printing function showFFromStrVec. It is a simplest multiplicative (somewhat acoustically and musically reasonable) form for the function that can provide such a result that fits into the given data.

let (y,f1) = fromJust (maybeFFromStrVec 1 3583.9783 "[(25.368,0.2486356),(37.259,0.6464867),(486.153,0.374618646),(789.563,0.463486461)]") in (y,f1 3583.9783)

(3520.0,[(25.829079975681818,0.2486356),(37.936206670369316,0.6464867),(494.9891484317899,0.374618646),(803.9138234326421,0.463486461)])

let (y,f1) = fromJust (maybeFFromStrVec (-1) 3583.9783 "[(25.368,0.2486356),(37.259,0.6464867),(486.153,0.374618646),(789.563,0.463486461)]") in (y,f1 3583.9783)

(3583.9783,[(25.368,0.2486356),(37.259,0.6464867),(486.153,0.374618646),(789.563,0.463486461)])

fVecCoefs :: Int -> Double -> String -> Vector Double Source #

Gets multiplication coefficients for f::Double -> Vector (Double,Double) from the maybeFFromStrVec with the same arguments.

showFFromStrVec :: Int -> Double -> String -> String Source #

Experimental show for f::Double -> Vector (Double,Double) that is used only for visualisation. It is correct only with maybeFFromStrVec or equivalent function. Because the shape of the f is known the function can be defined.

showFFromStrVec (-1) 440 "[(25.358,0.3598),(489.35,0.4588962),(795.35,0.6853)]"

"(440.00,(\t -> <(0.05763181818181818 * t, 0.3598),(1.112159090909091 * t, 0.4588962),(1.8076136363636364 * t, 0.6853)>))"

Functions to edit OvertonesO and function f (since 0.25.0.0)

renormF :: OvertonesO -> OvertonesO Source #

Renormalizes amplitudes for the frequencies so that the maximum one of them (if OvertonesO is not empty) is equal by the absolute value to 1.0 and the mutual ratios of the amplitudes are preserved.

renormFD :: Double -> OvertonesO -> OvertonesO Source #

Renormalizes amplitudes for the frequencies so that the maximum one of them (if OvertonesO is not empty) is equal by the absolute value to Double argument and the mutual ratios of the amplitudes are preserved.

sameOvertone :: OvertonesO -> Bool Source #

Predicate to check whether all tuples in a Vector have the same first element.

sameOvertoneL :: [(Double, Double)] -> Bool Source #

Similar to sameOvertone, except that not the Vector is checked but a corresponding list.

sameFreqF :: Double -> (Double, Double) -> (Double -> OvertonesO) -> ((Double, Double) -> OvertonesO -> OvertonesO) -> OvertonesO Source #

g :: (Double,Double) -> OvertonesO -> OvertonesO is a function that defines how the new element is added to the OvertonesO. It depends only on the element being added and the actual OvertonesO. It does not depend on the Double argument for f :: Double -> OvertonesO so for different Double for f it gives the same result.

sameFreqFI :: Double -> (Double, Double) -> (Double -> OvertonesO) -> ((Double, Double) -> OvertonesO -> OvertonesO) -> OvertonesO Source #

g :: (Double,Double) -> OvertonesO -> OvertonesO is a function that defines how the new element is added to the OvertonesO. Variant of sameFreqF where g depends only on the elements of the OvertonesO, which first elements in the tuples equal to the first element in the (Double,Double). It does not depend on the Double argument for f :: Double -> OvertonesO so for different Double for f it gives the same result.

fAddFElem :: (Double, Double) -> (Double -> OvertonesO) -> ((Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO) -> Double -> OvertonesO Source #

gAdd :: (Double,Double) -> Double -> (Double -> OvertonesO) -> OvertonesO is a function that defines how the element is added to the OvertonesO. fAddFElem is actually a higher-order function, it changes the function f and returns a new one. It can be an interesting task (in general) to look at such a function through a prism of notion of operator (mathematical, for example similar to that ones that are used for quantum mechanics and quantum field theory). gAdd allows not only to insert an element if missing, but to change all the OvertonesO system. So depending on the complexity, it can produce rather complex behaviour.

fRemoveFElem :: (Double, Double) -> (Double -> OvertonesO) -> ((Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO) -> Double -> OvertonesO Source #

gRem:: (Double,Double) -> Double -> (Double -> OvertonesO) -> OvertonesO is a function that defines how the element is removed from the OvertonesO. fRemoveFElem is actually a higher-order function, it changes the function f and returns a new one. It can be an interesting task (in general) to look at such a function through a prism of notion of operator (mathematical, for example that ones that are used for quantum mechanics and quantum field theory). gRem allows not only to delete an element if existing, but to change all the OvertonesO system. So depending on the complexity, it can produce rather complex behaviour.

fChangeFElem :: (Double, Double) -> Double -> (Double -> (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO) -> (Double -> OvertonesO) -> Double -> OvertonesO Source #

Changes elements of the OvertonesO using two functions. It is a generalization of the fAddFElem and fRemoveFElem functions. For example, if the first of the two inner functional arguments acts as gAdd01 or similar, then it adds element to the OvertonesO, if it acts as gRem01, then it removes the element. Its behaviour is defined by the Double parameter (meaning frequency, probably), so you can change elements depending on what point it is applied.

gAdd01 :: (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gAdd for the fAddFElem. If the frequency is already in the OvertonesO then the corresponding amplitude is divided equally between all the elements with the repeated given frequency from (Double, Double). Otherwise, it is just concatenated to the OvertonesO.

gAdd02 :: Double -> (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Can be used to produce an example of the function gAdd for the fAddFElem. Similar to gAdd01, but uses its first argument to renorm the result of the gAdd01 so that its maximum by absolute value amplitude equals to the first argument.

gAdd03 :: (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gAdd. for the fAddFElem. If the frequency is not already in the OvertonesO then the corresponding element is added and the OvertonesO are renormed with renormF. Otherwise, the element is tried to be inserted with a new frequency between the greatest by an absolute values notes as an intermediate value with the respective amplitude, or if there is only one element, to produce two elements in the resulting Vector with two consequent harmonics.

gAdd04 :: (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gAdd. for the fAddFElem. It tries to insert the given (Double,Double) into the less dense frequency region.

gRem01 :: (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gRem for the fRemoveFElem. If the element is already in the OvertonesO then it is removed (if there are more than 5 elements already) and OvertonesO are renormalized. Otherwise, all the same for the element already existing elements become less in an amlitude for a numbers that in sum equal to amplitude of the removed element.

gRem02 :: Double -> (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Can be used to produce an example of the function gRem for the fRemoveFElem. Similar to gRem01, but uses its first argument to renorm the result of the gRem01 so that its maximum by absolute value amplitude equals to the first argument.

gRem03 :: (Double, Double) -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gRem for the fRemFElem. It tries not to remove elements from the less than 6 elements OvertonesO and to remove all the elements in the given range with the width of the twice as many as the second Double in the first argument tuple and the centre in the first Double in the tuple. Similar to somewhat bandreject filter but with more complex behaviour for the sound to be more complex.

Working with two OvertonesO

fAddFElems :: OvertonesO -> (Double -> OvertonesO) -> (OvertonesO -> Double -> (Double -> OvertonesO) -> OvertonesO) -> Double -> OvertonesO Source #

Similar to fAddFElem, but instead of one element (Double,Double) it deals with a Vector of such elements that is OvertonesO.

fRemoveFElems :: OvertonesO -> (Double -> OvertonesO) -> (OvertonesO -> Double -> (Double -> OvertonesO) -> OvertonesO) -> Double -> OvertonesO Source #

Similar to fRemoveFElem, but instead of one element (Double,Double) it deals with a Vector of such elements that is OvertonesO.

fChangeFElems :: OvertonesO -> Double -> (Double -> OvertonesO -> Double -> (Double -> OvertonesO) -> OvertonesO) -> (Double -> OvertonesO) -> Double -> OvertonesO Source #

Similar to fChangeFElem, but use another form of the changing function, so it can deal with not only single element of the OvertonesO, but also with several ones.

freqsOverlapOvers :: OvertonesO -> OvertonesO -> Bool Source #

Binary predicate to check whether two given OvertonesO both have the elements with the same first element in the tuples. If True then this means that OvertonesO are at least partially overlaped by the first elements in the tuples (meaning frequencies).

elemsOverlapOvers :: OvertonesO -> OvertonesO -> Bool Source #

Similar to freqsOverlapOvers, but checks whether the whole tuples are the same instead of the first elements in the tuples are the same.

gAdds01 :: OvertonesO -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Example of the function gAdds for the fAddFElems.

gAdds02 :: Double -> OvertonesO -> Double -> (Double -> OvertonesO) -> OvertonesO Source #

Can be used to produce an example of the function gAdds for the fAddFElems. Similar to gAdds01, but uses its first argument to renorm the result of the gAdds01 so that its maximum by absolute value amplitude equals to the first argument.

Splitting and concatenating OvertonesO

splitO :: Int -> OvertonesO -> Vector OvertonesO Source #

Splits (with addition of the new overtones) a given OvertonesO into a number n (specified by the first Int argument) of OvertonesO (represented finally as a Vector of them respectively) so that all except the first n greatest by the absolute value of the amplitude tuples of Doubles are considered overtones for the greatest by the absolute value one in the given OvertonesO and all the next n - 1 are treated as the greatest by the absolute value and each of them produces the similar by the f :: Double -> OvertonesO function overtones.

It is expected to obtain by such a conversion a splitted one sound into several simultaneous similar ones with different heights. To provide a rich result, the given first argument must be strictly less than the length of the given OvertonesO minus one.

splitO2 :: (OvertonesO -> OvertonesO) -> Int -> OvertonesO -> Vector OvertonesO Source #

Splits (with addition of the new overtones) a given OvertonesO into a number of OvertonesO (represented finally as a Vector of them repsectively) so that it intermediately uses a special function before applying the "similarization" splitting function. Is a generalization of the splitO, which can be considered a splitO2 with a first command line argument equals to id.

It is expected to obtain by such a conversion a splitted one sound into several simultaneous similar (less or more, depending on h :: OvertonesO -> OvertonesO) ones with different heights. To provide a rich result, the given first argument must be strictly less than the length of the given OvertonesO minus one.

overConcat :: Vector OvertonesO -> OvertonesO Source #

Concatenates a Vector of OvertonesO into a single OvertonesO. Can be easily used with splitO.

Generalization of the previous ones splitting functions

splitHelp1 :: Int -> Int -> Int -> Int -> OvertonesO -> (Double, Double) -> Vector OvertonesO Source #

Auxiliary function that is used inside splitOG1.

splitHelp2 :: (OvertonesO -> OvertonesO) -> Int -> Int -> Int -> Int -> OvertonesO -> (Double, Double) -> Vector OvertonesO Source #

Auxiliary function that is used inside splitOG2.

splitOG1 :: String -> Int -> OvertonesO -> Vector OvertonesO Source #

Generalized variant of the splitO with the different splitting variants depending on the first two ASCII lower case letters in the String argument.

splitOG2 :: (OvertonesO -> OvertonesO) -> String -> Int -> OvertonesO -> Vector OvertonesO Source #

Generalized variant of the splitO2 with the different splitting variants depending on the first two ASCII lower case letters in the String argument.

splitOG12 :: (Int, Int, Int, Int) -> Vector (String, Int -> OvertonesO -> (Int, Int, Int, Int)) -> String -> Int -> OvertonesO -> Vector OvertonesO Source #

Generalized variant of the splitOG1 with a possibility to specify a default value for splitting parameters as the first argument (Int,Int,Int,Int) and the sorted by the first element in the tuple (actually a String) in ascending order Vector (the second one). Each String in the Vector must be unique and consist of lowercase ASCII letters.

splitOG12S :: (Int, Int, Int, Int) -> Vector (String, Int -> OvertonesO -> (Int, Int, Int, Int)) -> String -> Int -> OvertonesO -> Vector OvertonesO Source #

Variant of the splitOG12 applied to the unsorted second argument. It sorts it internally. If you specify the already sorted second argument then it is better to use splitOG12. Each String in the Vector must be unique and consist of lowercase ASCII letters.

splitOG22 :: (Int, Int, Int, Int) -> Vector (String, Int -> OvertonesO -> (Int, Int, Int, Int)) -> (OvertonesO -> OvertonesO) -> String -> Int -> OvertonesO -> Vector OvertonesO Source #

Generalized variant of the splitOG2 with a possibility to specify a default value for splitting parameters as the first argument (Int,Int,Int,Int) and the sorted by the first element in the tuple (actually a String) in ascending order Vector (the second one). Each String in the Vector must be unique and consist of lowercase ASCII letters.

splitOG22S :: (Int, Int, Int, Int) -> Vector (String, Int -> OvertonesO -> (Int, Int, Int, Int)) -> (OvertonesO -> OvertonesO) -> String -> Int -> OvertonesO -> Vector OvertonesO Source #

Variant of the splitOG22 applied to the unsorted second argument. It sorts it internally. If you specify the already sorted second argument then it is better to use splitOG22. Each String in the Vector must be unique and consist of lowercase ASCII letters.

New functions for the version 0.36.0.0

duration1000 :: FilePath -> IO Int Source #

Auxiliary function to get from a sound file specified a duration parameter n that can be used further.

durationsAver :: Durations -> Double -> Durations Source #

Durations accounting the desired average duration.

str2Durat1 :: String -> Double Source #

A conversion to the Double that is used inside str2Durations.

str2Durations :: String -> Double -> Durations Source #

A full conversion to the Durations from a Ukrainian text.

str2DurationsDef :: Int -> String -> Double -> Durations Source #

A default way to get Durations for the sounds up to 0.35.2.0 version of the package including. It is based on the number of Ukrainian sounds representations (see, convertToProperUkrainian) in a Ukrainian syllables or somewhat generated by the same rules as they. The rhythm using the function is very often not binary but its ratios are almost always a ratios of the small natural numbers (1, 2, 3, 4, 5, 6, 7 etc.).

str2Vol1 :: String -> Double Source #

A conversion to the Double that is used inside str2Volume.

str2Volume :: String -> Strengths Source #

A full conversion to the Strengths from a Ukrainian text.

defInt :: Intervals Source #

Default values for strToInt. All the intervals are not greater than one full octave.

doublesAveragedA :: Vector Double -> Double -> Vector Double Source #

Arithmetic average for the Vector is used as a weight for a duration.

doublesAveragedG :: Vector Double -> Double -> Vector Double Source #

Geometric average for the Vector is used as a weight for a strength.

equalize2Vec :: Vector (Vector a) -> Vector (Vector a) Source #

Auxiliar function to make all vectors in a Vector equal by length (the minimum one).

intervalsFromStringG :: Intervals -> String -> Intervals Source #

Generatlized version of the intervalsFromString with a possibility to specify your own Intervals.

overSoXSynthGen2FDN4G :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> Durations -> String -> IO () Source #

Generalized variant of the overSoXSynthGen2FDN with your own specified Durations for the sounds and pauses. Instead of using a Ukrainian text to specify a durations for the sounds (and a rhythm respectively) you provide your own rhythm as Durations. Positive values correspond to durations of the sounds generated and negative values -- to durations of the pauses respectively.

overSoXSynthGen2FDN_SG4GS :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO ()) -> IO () Source #

A variant of the overSoXSynthGen2FDN_SG4G where instead of providing your own durations as Durations you use a Ukrainian text and a function treats each symbol in it as a duration parameter with its sign. Positive values correspond to durations of the sounds generated and negative values -- to durations of the pauses respectively. Please, use a function h :: ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO ()) such that it can create for the given values accorgingly sounds and pauses. Otherwise, please, check whether at least it can deal with such arguments without errors.

silentSound2G :: FilePath -> Double -> String -> IO () Source #

For the given non-existing FilePath for a sound file supported by SoX generates a silence of the specified duration and quality (see, soxBasicParams).

strToIntG :: Intervals -> String -> Int Source #

Generatlized version of the strToInt with a possibility to specify your own Intervals.

strengthsAver :: Strengths -> Double -> Strengths Source #

Strengths accounting the desired average strength.

strengthsDbAver :: StrengthsDb -> Double -> StrengthsDb Source #

StrengthsDb accounting the desired average strength in dB.

vStrToVIntG :: Intervals -> Vector String -> Intervals Source #

Generatlized version of the vStrToVInt with a possibility to specify your own Intervals.

New generalized 5G functions that works with Intervals

overSoXSynth2FDN5G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> Vector Double -> String -> IO () Source #

Similar to overSoXSynth2FDN2G, but additionally allows to specify by the Intervals argument to specify your own intervals. For more information, please, refer to intervalsFromStringG.

overSoXSynth2FDN_B5G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> Vector Double -> String -> IO () Source #

Generalized version of the overSoXSynth2FDN_B2G with a possibility to specify your own Intervals. For more information, please, refer to intervalsFromStringG.

overSoXSynth2FDN_S5G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> Vector Double -> String -> IO () Source #

Generalized version of the overSoXSynth2FDN_S2G where you specify your own Intervals. For more information, please, refer to intervalsFromStringG.

overSoXSynth2FDN_Sf35G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> Vector Double -> String -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf31G with a possibility to specify sound quality using the second String parameter. For more information, please, refer to soxBasicParams.

New generalized 6G functions that works with Strengths

apply6Gf :: Double -> FilePath -> IO () Source #

Apply volume adjustment to the sound file. It must not be silent. Otherwise, it leads to likely noise sounding or errors.

apply6G :: Strengths -> String -> String -> IO () Source #

After producing sounds as WAV or FLAC files you can apply to them volume adjustments using Strengths. The first String is used accordingly to soxBasicParams and the second one -- as a prefix of the filenames for the files that the function is applied to. The files must not be silent ones. Otherwise, it leads to likely noise sounding or errors.

apply6G2 :: Strengths -> String -> String -> Double -> IO () Source #

Variant of the apply6G function which can be applied also to the silent files. Whether a file is silent is defined using the Double argument so that if a maximum by absolute value amplitude is less by absolute value than the Double argument then the file is not changed.

apply6GS :: String -> String -> String -> IO () Source #

Variant of the apply6G where you use as a Strengths parameter that one obtained from a Ukrainian text provided as a first String argument. It uses str2Volume inside. The files must not be silent ones. Otherwise, it leads to likely noise sounding or errors.

apply6GS2 :: String -> String -> String -> Double -> IO () Source #

Variant of the apply6G2 where you use as a Strengths parameter that one obtained from a Ukrainian text provided as a first String argument. It uses str2Volume inside.

overSoXSynth2FDN6G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> Vector Double -> String -> Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN5G with afterwards apply6Gf usage.

overSoXSynth2FDN6GS :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> String -> Vector Double -> String -> String -> IO () Source #

A variant of the overSoXSynth2FDN6G where volume adjustment is obtained from a Ukrainian text.

overSoXSynth2FDN_B6G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> Vector Double -> String -> Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN_B5G with afterwards apply6G usage.

overSoXSynth2FDN_B6GS :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> String -> Vector Double -> String -> String -> IO () Source #

A variant of the overSoXSynth2FDN_B6G where volume adjustment is obtained from a Ukrainian text.

overSoXSynth2FDN_S6G :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> Vector Double -> String -> Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN_S5G with afterwards apply6G usage. Arguments for the latter is the three last function arguments.

overSoXSynth2FDN_S6GS :: (Double -> OvertonesO) -> (Double, Double) -> Int -> Intervals -> String -> Vector Double -> String -> String -> IO () Source #

A variant of the overSoXSynth2FDN_S6G where volume adjustment is obtained from a Ukrainian text.

overSoXSynth2FDN_Sf36G :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> Vector Double -> String -> Double -> IO () Source #

Generalized variant of the overSoXSynth2FDN_Sf35G with afterwards apply6G usage.

overSoXSynth2FDN_Sf36GS :: (Double -> OvertonesO) -> (Double, Double, Double) -> Int -> Intervals -> String -> Vector Double -> String -> String -> IO () Source #

A variant of the overSoXSynth2FDN_Sf36G where volume adjustment is obtained from a Ukrainian text.

overSoXSynthGen2FDN_SG6G :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> Durations -> String -> ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO ()) -> Strengths -> Double -> IO () Source #

6G generalized variant of the overSoXSynthGen2FDN_SG4G with volume adjustments given by 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.

overSoXSynthGen2FDN_SG6GS :: FilePath -> Int -> Int -> (Double -> OvertonesO) -> Double -> String -> String -> ((Double -> OvertonesO) -> (Double, Double) -> Int -> String -> IO ()) -> String -> Double -> IO () Source #

A variant of the overSoXSynthGen2FDN_SG6G where Strengths are obtained from a Ukrainian text and str2Volume.