Copyright | (c) OleksandrZhabenko 2020 |
---|---|
License | MIT |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Maintainer : olexandr543@yahoo.com
A program and a library to create experimental music from a mono audio and a Ukrainian text.
Synopsis
- dobutokO2 :: IO ()
- recAndProcess :: String -> Int -> IO String
- oberTones :: Double -> Vector (Double, Double)
- oberSoXSynth :: Double -> IO ()
- oberSoXSynthN :: Int -> Double -> Double -> String -> Vector Double -> IO ()
- oberTones2 :: Double -> String -> Vector (Double, Double)
- oberSoXSynth2 :: Double -> String -> IO ()
- oberSoXSynthN2 :: Int -> Double -> Double -> String -> String -> Vector Double -> IO ()
- oberSoXSynthN3 :: Int -> Double -> Double -> Double -> String -> String -> String -> Vector Double -> IO ()
- oberSoXSynthDN :: Double -> String -> IO ()
- oberSoXSynth2DN :: Double -> Double -> String -> IO ()
- oberSoXSynth2FDN :: (Double -> Vector (Double, Double)) -> Double -> Double -> String -> IO ()
- oberSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> IO ()
- oberSoXSynthNGen2 :: FilePath -> Int -> Double -> Double -> String -> String -> IO ()
- oberSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> Double -> String -> String -> String -> IO ()
- uniqOberTonesV :: Double -> String -> Vector (Double, Double)
- uniqOberSoXSynth :: Double -> String -> IO ()
- uniqOberSoXSynthN :: Int -> Double -> Double -> String -> String -> Vector Double -> IO ()
- uniqOberTonesV2 :: Double -> String -> String -> Vector (Double, Double)
- uniqOberSoXSynth2 :: Double -> String -> String -> IO ()
- uniqOberSoXSynthN3 :: Int -> Double -> Double -> String -> String -> String -> Vector Double -> IO ()
- uniqOberSoXSynthN4 :: Int -> Double -> Double -> Double -> String -> String -> String -> String -> Vector Double -> IO ()
- uniqOberSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> String -> IO ()
- uniqOberSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> String -> String -> String -> IO ()
- octavesT :: Vector (Double, Double)
- octaveUp :: Double -> Double
- octaveDown :: Double -> Double
- whichOctave :: Double -> Maybe Int
- putInOctave :: Int -> Double -> Maybe Double
- putInOctaveV :: Int -> Vector Double -> Vector Double
- notes :: Vector Double
- neighbourNotes :: Double -> Vector Double -> (Double, Double)
- closestNote :: Double -> Double
- pureQuintNote :: Double -> Double
- syllableStr :: Int -> String -> [Int]
- signsFromString :: Int -> String -> Vector Int
- prependZeroes :: Int -> String -> String
- intervalsFromString :: String -> Vector Int
- dNote :: Int -> Double -> Maybe Double
Basic functions for the executable
Function that actually makes processing in the dobutokO2
executable. 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.
recAndProcess :: String -> Int -> IO String Source #
Function records and processes the sound data needed to generate the "end.wav" file in the dobutokO2
function. Please, check before executing
whether there is no "x.wav" file in the current directory, because it can be overwritten.
Library and executable functions
For the fixed timbre
oberTones :: Double -> Vector (Double, Double) 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.
oberSoXSynth :: 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.
oberSoXSynthN :: Int -> Double -> Double -> String -> Vector Double -> IO () Source #
Function to create a melody for the given arguments. String
is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
can be in the same octave or in the one with the number lower by one. The first Double
argument from the range [0.01..1.0] is used as a maximum amplitude
for obertones. If it is set to 1.0 the obertones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
in their becoming more silent ones. The second Double
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 the fixed timbre with different signs for harmonics coefficients
oberSoXSynth2 :: Double -> String -> 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.
The String
argument is used to define signs of the harmonics coefficients for obertones.
oberSoXSynthN2 :: Int -> Double -> Double -> String -> String -> Vector Double -> IO () Source #
Function to create a melody for the given arguments. String
is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
can be in the same octave or in the one with the number lower by one. The first Double
argument from the range [0.01..1.0] is used as a maximum amplitude
for obertones. If it is set to 1.0 the obertones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
in their becoming more silent ones. The second Double
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.
oberSoXSynthN3 :: Int -> Double -> Double -> Double -> String -> String -> String -> Vector Double -> IO () Source #
Function to create a melody for the given arguments. String
is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
can be in the same octave or in the one with the number lower by one. The first Double
argument from the range [0.01..1.0] is used as a maximum amplitude
for obertones. If it is set to 1.0 the obertones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
in their becoming more silent ones. The second Double
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.
The third String
argument is used to define the intervals for the notes if any.
The third Double
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 obertones are greater than for the main note obetones.
The last one is experimental feature.
Use additional parameters
oberSoXSynthDN :: Double -> String -> IO () Source #
Similar to oberSoXSynth
except that takes not necessarily pure lower quint note as the second one, but the one specified by the String
parameter
as an argument to dNote
. If you begin the String
with space characters, or "сь", or "ць", or dash, or apostrophe, or soft sign, than there will
be no interval and the sound will be solely one with its obertones.
oberSoXSynth2DN :: Double -> Double -> String -> IO () Source #
Similar to oberSoXSynthDN
except that the resulting duration is specified by the second Double
parameter in seconds. For oberSoXSynthDN
it is equal to 0.5.
Use additional function as a parameter
oberSoXSynth2FDN :: (Double -> Vector (Double, Double)) -> Double -> Double -> String -> IO () Source #
Similar to oberSoXSynth2DN
but instead of oberTones
function, it uses volatile function f::Double -> Vector (Double, Double)
with
somewhat sophisticated mechanism to normalize the resulting 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
.
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.
Use a file for information
oberSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> IO () Source #
Similar to oberSoXSynthN
, but uses a sound file to obtain the information analogous to Vector
in the latter one. Besides, the function lifts
the frequencies to the octave with the given by Int
parameter number (better to use from the range [1..8]). The first Double
argument from
the range [0.01..1.0] is used as a maximum amplitude for obertones. If it is set to 1.0 the obertones amplitudes are just maximum ones,
otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
The second Double
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.
oberSoXSynthNGen2 :: FilePath -> Int -> Double -> Double -> String -> String -> IO () Source #
Similar to oberSoXSynthN2
, but uses a sound file to obtain the information analogous to Vector
in the latter one. Besides, the function lifts
the frequencies to the octave with the given by Int
parameter number (better to use from the range [1..8]). The first Double
argument from
the range [0.01..1.0] is used as a maximum amplitude for obertones. If it is set to 1.0 the obertones amplitudes are just maximum ones,
otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
The second Double
argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
whether there is no "x.wav", "test*", "result*" and "end.wav" files in the current directory, because they can be overwritten.
For better usage the FilePath
should be a filepath for the .wav file.
The second String
argument is used to define signs of the harmonics coefficients in the generated sounds.
oberSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> Double -> String -> String -> String -> IO () Source #
Similar to oberSoXSynthN2
, but uses a sound file to obtain the information analogous to Vector
in the latter one. Besides, the function lifts
the frequencies to the octave with the given by Int
parameter number (better to use from the range [1..8]). The first Double
argument from
the range [0.01..1.0] is used as a maximum amplitude for obertones. If it is set to 1.0 the obertones amplitudes are just maximum ones,
otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
The second Double
argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
whether there is no "x.wav", "test*", "result*" and "end.wav" files in the current directory, because they can be overwritten.
For better usage the FilePath
should be a filepath for the .wav file.
The second String
argument is used to define signs of the harmonics coefficients in the generated sounds.
The third String
argument is used to define the intervals for the notes if any.
The third Double
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 obertones are greater than for the main note obetones.
The last one is experimental feature.
For the unique for the String structure timbre
uniqOberSoXSynth :: Double -> String -> IO () Source #
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 mmsyn7s
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*" and "end.wav" files in the current directory, because they can be overwritten.
uniqOberSoXSynthN :: Int -> Double -> Double -> String -> String -> Vector Double -> IO () Source #
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 Double
argument from the range [0.01..1.0] is used as a maximum amplitude for obertones.
If it is set to 1.0 the obertones 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 Double
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 the unique for the String structure timbre with different signs for harmonics coefficients
uniqOberTonesV2 :: Double -> String -> String -> Vector (Double, Double) 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. For every given
first String
argument structure of the uniqueness (see the documentation for mmsyn7s
package and its Syllable
module) it produces the unique timbre.
The second String
is used to produce the signs for harmonics coefficients.
uniqOberSoXSynth2 :: Double -> String -> String -> IO () Source #
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 mmsyn7s
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*" and "end.wav" files in the current directory, because they can be overwritten.
The second String
argument is used to define signs for the harmonics coefficients for obertones.
uniqOberSoXSynthN3 :: Int -> Double -> Double -> String -> String -> String -> Vector Double -> IO () Source #
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 Double
argument from the range [0.01..1.0] is used as a maximum amplitude for obertones.
If it is set to 1.0 the obertones 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 Double
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.
The third String
argument is used to define signs of the harmonics coefficients in the generated sounds.
uniqOberSoXSynthN4 :: Int -> Double -> Double -> Double -> String -> String -> String -> String -> Vector Double -> IO () Source #
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 Double
argument from the range [0.01..1.0] is used as a maximum amplitude for obertones.
If it is set to 1.0 the obertones 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 Double
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.
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 Double
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 obertones are greater than for the main note obetones.
The last one is experimental feature.
Use a file for information
uniqOberSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> String -> IO () Source #
Similar to uniqOberSoXSynthN
, but uses a sound file to obtain the information analogous to Vector
in the latter one.
Besides, the function lifts the frequencies to the octave with the given by Int
parameter number (better to use from the range [1..8]).
The first Double
argument from the range [0.01..1.0] is used as a maximum amplitude for obertones. If it is set to 1.0 the
obertones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
The second Double
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.
uniqOberSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> String -> String -> String -> IO () Source #
Similar to uniqOberSoXSynthN
, but uses a sound file to obtain the information analogous to Vector
in the latter one.
Besides, the function lifts the frequencies to the octave with the given by Int
parameter number (better to use from the range [1..8]).
The first Double
argument from the range [0.01..1.0] is used as a maximum amplitude for obertones. If it is set to 1.0 the
obertones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
The second Double
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.
Work with octaves
octavesT :: Vector (Double, Double) Source #
Returns a Vector
of tuples with the lowest and highest frequencies for the notes in the octaves.
octaveUp :: Double -> Double Source #
Returns an analogous note in the higher octave (its frequency in Hz).
octaveDown :: Double -> Double Source #
Returns an analogous note in the lower octave (its frequency in Hz).
whichOctave :: Double -> Maybe Int Source #
Function can be used to determine to which octave (in the American notation for the notes, this is a number in the note written form,
e. g. for C4 this is 4) the frequency belongs (to be more exact, the closest note for the given frequency -- see closestNote
taking into account
its lower pure quint, which can lay in the lower by 1 octave). If it is not practical to determine the number, then the function returns Nothing
.
putInOctave :: Int -> Double -> Maybe Double Source #
Function lifts the given frequency to the given number of the octave (in American notation, from 0 to 8). This number is an Int
parameter.
The function also takes into account the lower pure quint for the closest note.
If it is not practical to determine the number, then the function returns Nothing
.
putInOctaveV :: Int -> Vector Double -> Vector Double Source #
Function lifts the Vector
of Double
representing frequencies to the given octave with the Int
number. Better to use numbers in the range [1..8].
The function also takes into account the lower pure quint for the obtained note behaviour. If it is not practical to determine the octave, the resulting
frequency is omitted from the resulting Vector
.
Auxiliary functions
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.
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.
signsFromString :: Int -> String -> Vector Int Source #
Additional function to produce signs from the given String
of the Ukrainian text. Ukrainian vowels and voiced consonants gives "+" sign (+1), voiceless
and sonorous consonants gives "-" sign (-1). Voiceless2 gives "0". Other symbols are not taken into account.
intervalsFromString :: String -> Vector Int Source #
Function is used to get numbers of intervals from a Ukrainian String
. It is used internally in the uniqOberSoXSynthN4
function.