algorithmic-composition-frequency-shift-0.1.0.0: Helps to create experimental music. Uses SoX inside.
Copyright(c) OleksandrZhabenko 2020-2021
LicenseMIT
Maintainerolexandr543@yahoo.com
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010
ExtensionsCpp

Composition.Sound.Presentation

Description

Helps to create experimental music. This module contains different representations for the data. Is rewritten from the dobutokO4 package.

Synopsis

Sound repesentations

data SoundI Source #

An Int parameter is an index of the SoundI sound file in the sorted in the ascending order Vector of them (the corresponding files or their names) representing the whole composition.

Instances

Instances details
Eq SoundI Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

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

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

data SoundFN Source #

An FilePath parameter is a name of the sound file in the current directory with the filetype (supported by SoX) being given by String representing the whole composition.

Instances

Instances details
Eq SoundFN Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

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

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

data SoundT Source #

The first Float parameter is a time moment (starting from 0) of the playing the sound being represented by OvertonesO, the second one is its duration. The third one is its maximum amplitude by an absolute value. The fourth one is the minimum duration that can provide a needed human feeling of perception (some impression) for the sound. The further one(s) is(are) some adjustment(s) parameter(s).

Instances

Instances details
Eq SoundT Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

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

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

Sound time intervals representations

data Timity Source #

The first Float parameter is a time moment (starting from 0) of the playing the sound, the second one is its duration in seconds (with a negative values corresponding to the pause duration --- the silent "sound"), the third one is the minimum duration that can provide a needed human feeling of perception (some impression) for the sound.

Constructors

Time Float Float Float 

Instances

Instances details
Eq Timity Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

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

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

Ord Timity Source # 
Instance details

Defined in Composition.Sound.Presentation

Show Timity Source # 
Instance details

Defined in Composition.Sound.Presentation

data Timity1 a Source #

The first Float parameter is a time moment (starting from 0) of the playing the sound, the second one is its duration in seconds (with a negative values corresponding to the pause duration --- the silent "sound"), the third one is a parameter to specify more complex behaviour for the sound.

Constructors

Time1 Float Float a 

Instances

Instances details
Functor Timity1 Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

fmap :: (a -> b) -> Timity1 a -> Timity1 b #

(<$) :: a -> Timity1 b -> Timity1 a #

Eq a => Eq (Timity1 a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

(==) :: Timity1 a -> Timity1 a -> Bool #

(/=) :: Timity1 a -> Timity1 a -> Bool #

Ord a => Ord (Timity1 a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

compare :: Timity1 a -> Timity1 a -> Ordering #

(<) :: Timity1 a -> Timity1 a -> Bool #

(<=) :: Timity1 a -> Timity1 a -> Bool #

(>) :: Timity1 a -> Timity1 a -> Bool #

(>=) :: Timity1 a -> Timity1 a -> Bool #

max :: Timity1 a -> Timity1 a -> Timity1 a #

min :: Timity1 a -> Timity1 a -> Timity1 a #

Show a => Show (Timity1 a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

showsPrec :: Int -> Timity1 a -> ShowS #

show :: Timity1 a -> String #

showList :: [Timity1 a] -> ShowS #

Semigroup a => Semigroup (Timity1 a) Source #

Since base-4.9.0.0. Idempotent semigroup (band) (x <> x == x) if Semigroup a is idempotent (is a band).

Instance details

Defined in Composition.Sound.Presentation

Methods

(<>) :: Timity1 a -> Timity1 a -> Timity1 a #

sconcat :: NonEmpty (Timity1 a) -> Timity1 a #

stimes :: Integral b => b -> Timity1 a -> Timity1 a #

data IntervalTim Source #

Float interval representation with no order of the arguments preserved.

Constructors

Empty 
I Float Float 
UniversalI 

data IntervalTimI Source #

Another Float interval representation with no order of the arguments preserved. Since base-4.9.0.0 has different instance of Semigroup than IntervalTim.

Constructors

Empty2 
II Float Float 
UniversalII 

Instances

Instances details
Eq IntervalTimI Source # 
Instance details

Defined in Composition.Sound.Presentation

Ord IntervalTimI Source # 
Instance details

Defined in Composition.Sound.Presentation

Show IntervalTimI Source # 
Instance details

Defined in Composition.Sound.Presentation

Semigroup IntervalTimI Source #

Since base-4.9.0.0. Idempotent semigroup (x <> x == x) -- band. (<>) can be understood as an intersection of the sets.

Instance details

Defined in Composition.Sound.Presentation

Monoid IntervalTimI Source #

Can be understood as an intersection of the sets.

Instance details

Defined in Composition.Sound.Presentation

data IntervalG a b Source #

Generalized interval representation.

Constructors

IG a b 

Instances

Instances details
Bifunctor IntervalG Source #

Since base-4.8.0.0.

Instance details

Defined in Composition.Sound.Presentation

Methods

bimap :: (a -> b) -> (c -> d) -> IntervalG a c -> IntervalG b d #

first :: (a -> b) -> IntervalG a c -> IntervalG b c #

second :: (b -> c) -> IntervalG a b -> IntervalG a c #

Functor (IntervalG a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

fmap :: (a0 -> b) -> IntervalG a a0 -> IntervalG a b #

(<$) :: a0 -> IntervalG a b -> IntervalG a a0 #

(Eq a, Eq b) => Eq (IntervalG a b) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

(==) :: IntervalG a b -> IntervalG a b -> Bool #

(/=) :: IntervalG a b -> IntervalG a b -> Bool #

(Ord a, Ord b) => Ord (IntervalG a b) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

compare :: IntervalG a b -> IntervalG a b -> Ordering #

(<) :: IntervalG a b -> IntervalG a b -> Bool #

(<=) :: IntervalG a b -> IntervalG a b -> Bool #

(>) :: IntervalG a b -> IntervalG a b -> Bool #

(>=) :: IntervalG a b -> IntervalG a b -> Bool #

max :: IntervalG a b -> IntervalG a b -> IntervalG a b #

min :: IntervalG a b -> IntervalG a b -> IntervalG a b #

(Show a, Show b) => Show (IntervalG a b) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

showsPrec :: Int -> IntervalG a b -> ShowS #

show :: IntervalG a b -> String #

showList :: [IntervalG a b] -> ShowS #

Semigroup (IntervalG a b) Source #

Since base-4.9.0.0. Idempotent semigroup (x <> x == x) and rectangular band (x <> y <> z == x <> z) For more information, please, refer to: https://en.wikipedia.org/wiki/Band_(mathematics)

Instance details

Defined in Composition.Sound.Presentation

Methods

(<>) :: IntervalG a b -> IntervalG a b -> IntervalG a b #

sconcat :: NonEmpty (IntervalG a b) -> IntervalG a b #

stimes :: Integral b0 => b0 -> IntervalG a b -> IntervalG a b #

data IntervalMG a Source #

Generalized interval representation which is a Monoid instance.

Constructors

IMG a a 
UniversalG 

Instances

Instances details
Eq a => Eq (IntervalMG a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Methods

(==) :: IntervalMG a -> IntervalMG a -> Bool #

(/=) :: IntervalMG a -> IntervalMG a -> Bool #

Ord a => Ord (IntervalMG a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Show a => Show (IntervalMG a) Source # 
Instance details

Defined in Composition.Sound.Presentation

Semigroup (IntervalMG a) Source #

Since base-4.9.0.0. Idempotent semigroup (x <> x == x) and rectangular band (x <> y <> z == x <> z) For more information, please, refer to: https://en.wikipedia.org/wiki/Band_(mathematics)

Instance details

Defined in Composition.Sound.Presentation

Monoid (IntervalMG a) Source # 
Instance details

Defined in Composition.Sound.Presentation