algorithmic-composition-complex-0.2.0.0: Helps to create more complex experimental music from a file (especially timbre).
Copyright(c) OleksandrZhabenko 2020-2022
LicenseMIT
Maintainerolexandr543@yahoo.com
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

Composition.Sound.Complex

Description

Helps to create experimental music from a file (or its part). Uses SoX inside. Is more complicated than algorithmic-composition-basic and uses its functionality.

Synopsis

Another way to generalize the simple functions of dobutokO2 package

testSoundGen2G :: FilePath -> Float -> String -> IO () Source #

Tesing variant of the soundGen3G with predefined three last functional arguments.

soundGen3G :: FilePath -> Float -> String -> ((Float, Float) -> Float -> (Float -> OvertonesO) -> OvertonesO) -> ((Float, Float) -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generates a sequence of sounds with changing timbre. Uses several functions as parameters.

soundGen3G_O :: Int -> Int -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generates a sequence of sounds with changing timbre. Uses several functions as parameters. Unlike the soundGen3G, the last two functions as arguments for their first argument have not (Float,Float), but Vector of them so are applied to OvertonesO. To provide a generalized functionality, it uses two additional functions freq0 :: Int -> OvertonesO and proj :: OvertonesO -> OvertonesO to define the first element to which are applied gAdds and gRems and the way to obtain a internal OvertonesO. Besides, it lifts notes into specified with the first two Int arguments enku (see liftInEnku). The Float argument is a average duration of the sounds.

soundGen3G_O2 :: ((Float -> OvertonesO, Int -> Float -> OvertonesO, Int -> Float -> OvertonesO) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> Int -> Int -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generates a sequence of sounds with changing timbre. Is a generalized version of the soundGen3G_O, instead of predefined conversion function inside, it uses a user-defined one.

soundGen3G_O = soundGen3G_O2 

with the first argument

conversionFII (f0,fA1,fR1) = map (\(j, r) -> (GHC.Arr.unsafeAt notes (snd r),
     case fst r of
       0 -> f0
       1 -> fA1 j
       2 -> fA1 j
       3 -> fA1 j
       4 -> fA1 j
       _ -> fR1 j)) . zip [0..]

soundGen3G_O2G :: (([Float -> OvertonesO], [Int -> Float -> OvertonesO], [Int -> Float -> OvertonesO]) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> [Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> Int -> Int -> Float -> FilePath -> Float -> String -> IO () Source #

Generates a sequence of sounds with changing timbre. Is a generalized version of the soundGen3G_O2, but for the conversion function conversionFII as its tuple first argument uses not the tuple of the three functions, but a tuple of three lists of functions of the respective types, that allows to specify more comlex behaviour and different variants inside the function itself, not its inner function parts. Vector as a data type is used instead of more common list because it has similar functionality and besides provides easier and quicker access to its elements. So these are the following vectors of functions: vf :: Vector (Float -> OvertonesO) (no changing a function for timbre generation), vfA :: Vector (Int -> Float -> OvertonesO) (for "adding" overtones to the function for timbre generation), and vfR :: Vector (Int -> Float -> OvertonesO (for "removing" overtones from the function for timbre generation).

With MN control

testSoundGen2GMN :: Int -> Int -> FilePath -> Float -> String -> IO () Source #

Tesing variant of the soundGen3GMN with predefined last functional arguments.

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

Generates a sequence of sounds with changing timbre. Uses several functions as parameters. To specify how many sounds the resulting files will provide, you use first two Int arguments, the first of which is a number of dropped elements for readFileDoubles and the second one is a number of produced sounds (and, respectively, number of taken elements).

soundGen3G_OMN :: Int -> Int -> Int -> Int -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generates a sequence of sounds with changing timbre. Uses several functions as parameters. To specify how many sounds the resulting files will provide, you use first two Int arguments, the first of which is a number of dropped elements for readFileDoubles and the second one is a number of produced sounds (and, respectively, number of taken elements).

soundGen3G_O2MN :: Int -> Int -> ((Float -> OvertonesO, Int -> Float -> OvertonesO, Int -> Float -> OvertonesO) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> Int -> Int -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generates a sequence of sounds with changing timbre. Is a generalized version of the soundGen3G_O2. To specify how many sounds the resulting files will provide, you use first two Int arguments, the first of which is a number of dropped elements for readFileDoubles and the second one is a number of produced sounds (and, respectively, number of taken elements).

soundGen3G_O2GMN :: Int -> Int -> (([Float -> OvertonesO], [Int -> Float -> OvertonesO], [Int -> Float -> OvertonesO]) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> [Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> Int -> Int -> Float -> FilePath -> Float -> String -> IO () Source #

Generates a sequence of sounds with changing timbre. Is a generalized version of the soundGen3G_O2G. To specify how many sounds the resulting files will provide, you use first two Int arguments, the first of which is a number of dropped elements for readFileDoubles and the second one is a number of produced sounds (and, respectively, number of taken elements).

h1 :: (Float -> OvertonesO) -> (Float, Float) -> IO () Source #

For the given parameters generates a single sound with overtones or pause depending on the sign of the second element in the tuple of Float: if it is greater than zero then the sound is generated, if less -- the silence (pause), if it is equal to zero then it prints an informational message about a non-standard situation.

h2 :: OvertonesO -> (Float, Float) -> Int -> Int -> Float -> IO () Source #

For the given parameters generates a single sound with overtones or pause depending on the sign of the second element in the tuple of Float: if it is greater than zero then the sound is generated, if less -- the silence (pause), if it is equal to zero then it prints an informational message about a non-standard situation. Unlike the h1 function, it lifts the frequency into the enku specified by the Int arguments (see liftInEnku).

With Params control

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

Generalized version of the soundGen3G_O where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

soundGen3G_O2Par :: ((Float -> OvertonesO, Int -> Float -> OvertonesO, Int -> Float -> OvertonesO) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> Params -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generalized version of the soundGen3G_O2 where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

soundGen3G_O2GPar :: (([Float -> OvertonesO], [Int -> Float -> OvertonesO], [Int -> Float -> OvertonesO]) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> [Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> Params -> Float -> FilePath -> Float -> String -> IO () Source #

Generalized version of the soundGen3G_O2G where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

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

Generalized version of the soundGen3G_OMN where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

soundGen3G_O2MNPar :: Int -> Int -> ((Float -> OvertonesO, Int -> Float -> OvertonesO, Int -> Float -> OvertonesO) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> Params -> Float -> FilePath -> Float -> String -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (OvertonesO -> Float -> (Float -> OvertonesO) -> OvertonesO) -> (Int -> OvertonesO) -> (OvertonesO -> OvertonesO) -> (Float -> OvertonesO) -> IO () Source #

Generalized version of the soundGen3G_O2MN where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

soundGen3G_O2GMNPar :: Int -> Int -> (([Float -> OvertonesO], [Int -> Float -> OvertonesO], [Int -> Float -> OvertonesO]) -> [(Int, Int)] -> [(Float, Float -> OvertonesO)]) -> [Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> [Int -> Float -> OvertonesO] -> Params -> Float -> FilePath -> Float -> String -> IO () Source #

Generalized version of the soundGen3G_O2GMN where liftInParams is used instead of lifting with the liftInEnku. This allows e. g. to use some tonality. For more information, please, refer to filterInParams.

h2Params :: OvertonesO -> (Float, Float) -> Params -> Float -> IO () Source #

For the given parameters generates a single sound with overtones or pause depending on the sign of the second element in a tuple of Float: if it is greater than zero then the sound is generated, if less -- the silence (pause), if it is equal to zero then it prints an informational message about a non-standard situation. Unlike the h1 function, it lifts into the requency specified by the Params argument .