dobutokO2-0.24.3.0: A program and a library to create experimental music from a mono audio and a Ukrainian text

Copyright(c) OleksandrZhabenko 2020
LicenseMIT
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

DobutokO.Sound.Functional

Contents

Description

Maintainer : olexandr543@yahoo.com

A program and a library to create experimental music from a mono audio and a Ukrainian text.

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..

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.

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.

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.

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).

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 -> String -> Vector Double -> String -> IO () Source #

Generalized variant of the soundGenF31G with a possibility to specify sound quality using the second 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.

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.

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.

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 -> String -> 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.

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.

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 -> String -> 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

soxBasicParams :: String -> [String] -> [String] Source #

Is used internally in the functions to specify different SoX parameters for the sound synthesis (rate, bit depth and file extension). Possible file extensions are: ".wav" (a default one) and ".flac" (being lossless compressed); rates -- 8000, 11025, 16000, 22050 (a default one), 32000, 44100, 48000, 88200, 96000, 176400, 192000 Hz; bit depths -- 16 bits and 24 bits. The first two digits in a String argument encodes rate, the next one -- bit depth and the last symbol -- letter 'w' or 'f' -- file extension. Because of SoX uses FLAC optionally, before use it, please, check whether your installation supports it.

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.

intervalsFromString :: String -> Vector Int Source #

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

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

Generates a Vector of OvertonesO that represents the sound.

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)>))"