dobutokO2-0.43.0.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.Params

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. Is more complicated than dobutokO2 and uses its functionality.

Synopsis

Documentation

data Params Source #

Representation of the scales and modes for the notes. Can be extended further, but for a lot of situations the following realization is sufficient. See, for example, filterInParams and so on. String is (are) used as a general classification name, for some of them there are provided two String to classify. Lists are used to specify remainders in some meaning. See also, liftInParams and toneE (toneD) functions, elemP and elemCloseP, lengthP and showD.

Instances
Eq Params Source # 
Instance details

Defined in DobutokO.Sound.Functional.Params

Methods

(==) :: Params -> Params -> Bool #

(/=) :: Params -> Params -> Bool #

Ord Params Source # 
Instance details

Defined in DobutokO.Sound.Functional.Params

Show Params Source # 
Instance details

Defined in DobutokO.Sound.Functional.Params

Type synonyms with different semantics

type Durations = Vector Float 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 Float Source #

Is used to represent a set of volumes in the amplitude 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.

New generalizations for scales and modes with Params

filterInParams :: Params -> Maybe (Vector Float) Source #

A way to get from a Params a corresponding Vector of Float (if any) and so to work with them further. May contain some issues so please, before production usage check thoroughly. For information there were used the following:

https://en.wikipedia.org/wiki/Mode_(music)

https://en.wikipedia.org/wiki/Ukrainian_Dorian_scale

https://en.wikipedia.org/wiki/List_of_musical_scales_and_modes

https://en.wikipedia.org/wiki/Octatonic_scale

several other articles in the English Wikipedia

and in Ukrainian: Смаглій Г., Маловик Л. Теорія музики : Підруч. для навч. закл. освіти, культури і мистецтв / Г.А. Смаглій. -- Х. : Вид-во "Ранок", 2013. -- 392 с. ISBN 978-617-09-1294-7

sortNoDup :: Ord a => [a] -> [a] Source #

For the list of a from the Ord class it builds a sorted in the ascending order list without duplicates.

sortNoDup [2,1,4,5,6,78,7,7,5,4,3,2,5,4,2,4,54,3,5,65,4,3,54,56,43,5,2] = [1,2,3,4,5,6,7,43,54,56,65,78]

toneD :: Int -> Int -> Int -> [Int] -> Bool Source #

Checks whether its first Int argument does not belong to those ones that are included into the list argument on the reminders basis. The opposite to toneE with the same arguments.

toneE :: Int -> Int -> Int -> [Int] -> Bool Source #

Checks whether its first Int argument does belong to those ones that are included into the list argument on the reminders basis. The opposite to toneD with the same arguments.

liftInParams :: Float -> Params -> Float Source #

Analogous to liftInEnku lifts a frequency into a tonality (or something that can be treated alike one) specified by Params. If not reasonably one exists then the result is 11440 (Hz).

lengthP :: Params -> Int Source #

Gets a length of the Vector of Float being represented as Params. This is a number of the notes contained in the Params.

elemP :: Float -> Params -> Bool Source #

Check whether a given Float value (frequency of a note) is in the vector of Floats that corresponds to the given Params.

elemCloseP :: Float -> Params -> Bool Source #

Check whether a given Float value (frequency of the closest note to the given frequency) is in the vector of Floats that corresponds to the given Params.

showD :: Params -> String Source #

A way to show not the (somewhat algebraic) structure of the Params (as the usual show does), but the contained frequencies in it.

isStrParams :: String -> Params -> Bool Source #

Check whether for the given arguments there are the notes and whether String is a name signature for the scale in Params (can they be used together to correspond to a non-empty set of notes).

isListParams :: [Int] -> Params -> Bool Source #

Check whether for the given arguments there are the notes and whether list of Int is a part of the constructed Params (can they be used together to correspond to a non-empty set of notes).

Application of the Params

overSoXSynthGen2FDN_SG4GPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> Durations -> String -> ((Float -> OvertonesO) -> (Float, Float) -> Int -> String -> IO ()) -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_SG4G where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

overSoXSynthGen2FDN_SG6GPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> Durations -> String -> ((Float -> OvertonesO) -> (Float, Float) -> Int -> String -> IO ()) -> Strengths -> Float -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_SG6G where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

overSoXSynthGen2FDN_SG2GPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> String -> String -> ((Float -> OvertonesO) -> (Float, Float) -> Int -> String -> String -> IO ()) -> String -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_SG2G where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

overSoXSynthGen2FDN_SfPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> String -> String -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_Sf where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

overSoXSynthGen2FDN_Sf3GPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> Float -> String -> String -> ((Float -> OvertonesO) -> (Float, Float, Float) -> Int -> String -> IO ()) -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_Sf3G where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

overSoXSynthGen2FDN_Sf3G2GPar :: FilePath -> Params -> (Float -> OvertonesO) -> Float -> Float -> String -> String -> ((Float -> OvertonesO) -> (Float, Float, Float) -> Int -> String -> String -> IO ()) -> String -> IO () Source #

Generalized version of the overSoXSynthGen2FDN_Sf3G2G where instead of lifting with liftInEnkuV liftInParamsV is used. It allows e. g. to use some tonality. For more information, please, refer to filterInParams.

Creating melody from overtones

overMeloPar :: (Float -> OvertonesO) -> (Float -> Float) -> Params -> Float -> Float -> Float -> IO () Source #

Generates melody for the given parameters. The idea is that every application of the function f :: Float -> OvertonesO to its argument possibly can produce multiple overtones being represented as Vector of tuples of pairs of Float. We can use the first element in the tuple to obtain a new sound parameters and the second one -- to obtain its new duration in the melody. Additional function g :: Float -> Float is used to avoid the effect of becoming less and less -- closer to the zero for the higher overtones so the durations will become also less. Besides it allows to rescale the durations in a much more convenient way.

The first Float parameter is a multiplication coefficient to increase or to decrease the durations (values with an absolute values greater than one correspond to increasing inside the g. function applied afterwards with function composition and the values with an absolute values less than one and not equal to zero correspond to decreasing inside the g function. The second Float parameter is a usual frequency which is used instead of the 11440.0 (Hz) value. The third Float parameter is a main argument -- the frequency for which the OvertonesO are generated as a first step of the computation.

Additional functions

str2DurationsDef :: Int -> String -> Float -> 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.).

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.

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

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

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

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

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

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

defInt :: Intervals Source #

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

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.

overSoXSynth2FDN_Sf :: (Float -> OvertonesO) -> (Float, Float) -> 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 :: (Float -> OvertonesO) -> (Float, Float, Float) -> 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 Float parameter by an absolute value in the triple of Float'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.

overSoXSynth2FDN_Sf32G :: (Float -> OvertonesO) -> (Float, Float, Float) -> Int -> String -> Vector Float -> 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.

intervalsFromString :: String -> Intervals Source #

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

soundGenF32G :: Vector (Float -> Float) -> Vector Float -> Vector Int -> (Float -> OvertonesO) -> (Float, Float, Float) -> Int -> Vector Float -> 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.

doubleVecFromVecOfFloat :: (Float -> OvertonesO) -> Float -> Vector (Maybe Float) -> Vector OvertonesO Source #

Generates a Vector of OvertonesO that represents the sound.