Copyright | (c) Oleksandr Zhabenko 2021-2023 |
---|---|
License | MIT |
Maintainer | oleksandr.zhabenko@yahoo.com |
Stability | Experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions |
|
The module is highly experimental approach to estimate further the rhythmicity (using some extent of the music concept of polyrhythm) of the not very long lists (well, not longer than e. g. 30 elements). Is rather computationally expensive, so must be used with caution. If the period of rhythm is less than 5 or even 6 it is not effective.
Synopsis
- data Marker4s
- newtype PolyMarkers = PolyMs Char
- data PolyMrks
- = R4 Marker4s
- | RP PolyMarkers
- is4s :: PolyMrks -> Bool
- isPoly :: PolyMrks -> Bool
- data PolyRhythmBasis = PolyRhythm [Int]
- vals :: PolyRhythmBasis -> [Int]
- data PolyChoices = PolyCh {}
- validPolyChRhPair :: PolyChoices -> PolyRhythmBasis -> Bool
- data Intermediate a
- = J a
- | I PolyMarkers
- isJI :: Intermediate a -> Bool
- fromIntermediate :: Intermediate a -> Maybe PolyMrks
- getPolyChRhData :: Ord a => Char -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> [[PolyMrks]]
- increasingF :: Int -> Double -> Double
- increasingF1 :: Int -> Double -> Double
- increasingFG :: Int -> Double -> (Int -> Double -> Double -> Double) -> Double -> Double
- decreasingF1 :: Int -> Double -> Double
- decreasingFG :: Int -> Double -> (Int -> Double -> Double -> Double) -> Double -> Double
- decreasingFG2 :: Int -> Double -> (Double -> Double -> Double) -> Double -> Double
- increasingFG2 :: Int -> Double -> (Double -> Double -> Double) -> Double -> Double
- decreasingF :: Int -> Double -> Double
- similarityF1 :: Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityF0 :: Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFGE1 :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFG1 :: Double -> (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFG12 :: Double -> (Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFGE0 :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFG0 :: Double -> (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityFG02 :: Double -> (Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double
- similarityLogics :: Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogics0 :: Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsGE :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsG1 :: Double -> (Int -> Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsG12 :: Double -> (Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsGE0 :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsG0 :: Double -> (Int -> Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityLogicsG02 :: Double -> (Double -> Double -> Double) -> Char -> Double -> [PolyMrks] -> [PolyMrks] -> Double
- similarityPoly :: Char -> Double -> [[PolyMrks]] -> Double
- similarityPoly2 :: [PolyMrks] -> Char -> Double -> [[PolyMrks]] -> Double
- similarityPolyGEE :: (Int, [PolyMrks]) -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyGE :: Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyG1 :: (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyG12 :: (Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPoly0 :: Char -> Double -> [[PolyMrks]] -> Double
- similarityPoly20 :: [PolyMrks] -> Char -> Double -> [[PolyMrks]] -> Double
- similarityPolyGEE0 :: (Int, [PolyMrks]) -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyGE0 :: Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyG0 :: (Int -> Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- similarityPolyG02 :: (Double -> Double -> Double) -> Char -> Double -> [(Int, [PolyMrks])] -> Double
- rhythmicityPoly :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyGE :: Ord a => Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyG1 :: Ord a => (Int -> Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyG12 :: Ord a => (Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyGE0 :: Ord a => Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyG01 :: Ord a => (Int -> Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyG02 :: Ord a => (Double -> Double -> Double) -> Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPoly0 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- simpleF2 :: Double -> Double -> Double
- simpleF3 :: Int -> Double -> Double -> Double
- simpleEndF2 :: Double -> Double -> Double
- simpleEndF3 :: Int -> Double -> Double -> Double
- rhythmicityPolyWeightedF2 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedF3 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedF20 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedF30 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedEF2 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedEF3 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedEF20 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedEF30 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- linearF2 :: Double -> Double -> Double
- linearF3 :: Int -> Double -> Double -> Double
- linearEndF2 :: Double -> Double -> Double
- linearEndF3 :: Int -> Double -> Double -> Double
- rhythmicityPolyWeightedLF2 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLF3 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLF20 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLF30 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLEF2 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLEF3 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLEF20 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- rhythmicityPolyWeightedLEF30 :: Ord a => Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
- data ParseChRh
- isChRhString :: ParseChRh -> Bool
- isChRh3 :: ParseChRh -> Bool
- isChRhPoly :: ParseChRh -> Bool
- readRhythmicity :: String -> Maybe ParseChRh
Documentation
The data type that is used to mark the syllables accordingly to
their importance in general rhythm constituting. More important syllables
are marked with the less data constuctors (since the data type has an
instance of the Ord
type class). Contrary to PolyMarkers
and Marker3s
,
can be used in case of three levels of importance for rhythm constituting
with the last, fourth G
level of the syllables which position is thought as
not significant (though it actually, is not, but for simplicity).
newtype PolyMarkers Source #
The data type that is used to mark the syllables accordingly to
their importance in general rhythm constituting. More important syllables
are marked with the less data constuctors (since the data type has an
instance of the Ord
type class). A generalization of the
Marker4s
and Marker3s
for the cases of multiple (may be 4, or 3, or more)
levels of importance in general rhythm constituting.
Instances
Show PolyMarkers Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm showsPrec :: Int -> PolyMarkers -> ShowS # show :: PolyMarkers -> String # showList :: [PolyMarkers] -> ShowS # | |
Eq PolyMarkers Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm (==) :: PolyMarkers -> PolyMarkers -> Bool # (/=) :: PolyMarkers -> PolyMarkers -> Bool # | |
Ord PolyMarkers Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm compare :: PolyMarkers -> PolyMarkers -> Ordering # (<) :: PolyMarkers -> PolyMarkers -> Bool # (<=) :: PolyMarkers -> PolyMarkers -> Bool # (>) :: PolyMarkers -> PolyMarkers -> Bool # (>=) :: PolyMarkers -> PolyMarkers -> Bool # max :: PolyMarkers -> PolyMarkers -> PolyMarkers # min :: PolyMarkers -> PolyMarkers -> PolyMarkers # |
A data type is used to allow usage of the Marker4s
and PolyMarkers
data types in the
functions as just one single (unified) data type.
data PolyRhythmBasis Source #
Data to specify some quantitative information of the structure of rhythmicity.
Instances
Show PolyRhythmBasis Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm showsPrec :: Int -> PolyRhythmBasis -> ShowS # show :: PolyRhythmBasis -> String # showList :: [PolyRhythmBasis] -> ShowS # | |
Eq PolyRhythmBasis Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm (==) :: PolyRhythmBasis -> PolyRhythmBasis -> Bool # (/=) :: PolyRhythmBasis -> PolyRhythmBasis -> Bool # |
vals :: PolyRhythmBasis -> [Int] Source #
data PolyChoices Source #
Data to specify (mostly) the qualitative information of the structure of rhythmicity.
Instances
Eq PolyChoices Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm (==) :: PolyChoices -> PolyChoices -> Bool # (/=) :: PolyChoices -> PolyChoices -> Bool # |
:: PolyChoices | |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> Bool |
The predicate to check whether the two given arguments can be used together to get meaningful results.
The pqty
of the first argument must be equal to the sum
of the PolyRhythmBasis
Int
values
inside the list. There are also other logical constraints that the function takes into account.
data Intermediate a Source #
Auxiliary data type that is used internally in the getPolyChRhData
function in the module.
J a | |
I PolyMarkers |
Instances
Eq a => Eq (Intermediate a) Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm (==) :: Intermediate a -> Intermediate a -> Bool # (/=) :: Intermediate a -> Intermediate a -> Bool # | |
Ord a => Ord (Intermediate a) Source # | |
Defined in Phladiprelio.Rhythmicity.PolyRhythm compare :: Intermediate a -> Intermediate a -> Ordering # (<) :: Intermediate a -> Intermediate a -> Bool # (<=) :: Intermediate a -> Intermediate a -> Bool # (>) :: Intermediate a -> Intermediate a -> Bool # (>=) :: Intermediate a -> Intermediate a -> Bool # max :: Intermediate a -> Intermediate a -> Intermediate a # min :: Intermediate a -> Intermediate a -> Intermediate a # |
isJI :: Intermediate a -> Bool Source #
fromIntermediate :: Intermediate a -> Maybe PolyMrks Source #
:: Ord a | |
=> Char | The start of the |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> [[PolyMrks]] |
The more straightforward variant of the similarityF1
function.
similarityFGE1 :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
similarityFG1 :: Double -> (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
similarityFG12 :: Double -> (Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
similarityFGE0 :: Double -> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
similarityFG0 :: Double -> (Int -> Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
similarityFG02 :: Double -> (Double -> Double -> Double) -> Char -> PolyMrks -> PolyMrks -> Double -> Double Source #
:: Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one)
lists of PolyMrks
. Uses both increasing and decreasing functions.
:: Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
The more straightforward variant of the similarityLogics
function.
:: Double | |
-> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
:: Double | |
-> (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
:: Double | |
-> (Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
:: Double | |
-> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
The more straightforward variant of the similarityLogicsGE
function.
:: Double | |
-> (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
:: Double | |
-> (Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | An initial value. |
-> [PolyMrks] | |
-> [PolyMrks] | |
-> Double |
:: Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [[PolyMrks]] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one)
lists of PolyMrks
. Uses similarityLogics
inside.
:: [PolyMrks] | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [[PolyMrks]] | |
-> Double |
:: (Int, [PolyMrks]) | |
-> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: (Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [[PolyMrks]] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one)
lists of PolyMrks
. Uses similarityLogics0
inside.
The more straightforward variant of the similarityPoly
function.
:: [PolyMrks] | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [[PolyMrks]] | |
-> Double |
:: (Int, [PolyMrks]) | |
-> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: (Int -> Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: (Double -> Double -> Double) | |
-> Char | The start of the counting. |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> [(Int, [PolyMrks])] | |
-> Double |
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
General function to estimate the inner rhythmicity of the Ord
ered list of values. For many cases its arguments can be
guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one.
:: Ord a | |
=> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
General function to estimate the inner rhythmicity of the Ord
ered list of values. For many cases its arguments can be
guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one.
:: Ord a | |
=> (Int -> Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
:: Ord a | |
=> (Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
:: Ord a | |
=> Either (Double -> Double -> Double) (Int -> Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
General function to estimate the inner rhythmicity of the Ord
ered list of values. For many cases its arguments can be
guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one.
:: Ord a | |
=> (Int -> Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
:: Ord a | |
=> (Double -> Double -> Double) | |
-> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double | The greater one corresponds to (probably) more rhythmic list. |
General function to estimate the inner rhythmicity of the Ord
ered list of values. For many cases its arguments can be
guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one.
The more straightforward variant of the rhythmicityPoly
function.
simpleF2 :: Double -> Double -> Double Source #
This function tries to increase the importance of the beginning of the line and decreases the importance of the ending of the line. It is not a linear one.
simpleEndF2 :: Double -> Double -> Double Source #
This function tries to increase the importance of the ending of the line and decreases the importance of the beginning of the line. It is not a linear one.
rhythmicityPolyWeightedF2 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedF3 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedF20 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedF30 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedEF2 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedEF3 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedEF20 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedEF30 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
linearF2 :: Double -> Double -> Double Source #
This function tries to increase the importance of the beginning of the line and decreases the importance of the ending of the line. It is linear.
linearEndF2 :: Double -> Double -> Double Source #
This function tries to increase the importance of the ending of the line and decreases the importance of the beginning of the line. It is linear.
rhythmicityPolyWeightedLF2 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLF3 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLF20 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLF30 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLEF2 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLEF3 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLEF20 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
rhythmicityPolyWeightedLEF30 Source #
:: Ord a | |
=> Double | The initial value starting from which it counts. Usually, equals to 1.0. |
-> Int | If the argument is less or equal to 4, then |
-> PolyChoices | Data specifies the structure of the period of rhythmicity -- whether maximum or minimum elements are considered and how many syllables costitute the period. |
-> PolyRhythmBasis | Data specifies the quantities of the syllables on the corresponding levels of importance. |
-> [a] | |
-> Double |
Data type that is used to implement some parameter language to encode in the String
argument information
that is sufficient to transform the String
into Double
using the needed additional information provided by
some other means.
P0 String | |
P1 Choices RhythmBasis Int | The number of the one of the functions to convert the phonetic languages elements into |
P2 | |
|
isChRhString :: ParseChRh -> Bool Source #
isChRhPoly :: ParseChRh -> Bool Source #
readRhythmicity :: String -> Maybe ParseChRh Source #
A parser function to get the ParseChRh
data. In case of success returns Just
ParseChRh
value.
Nevertheless, the further checks (e. g. validPolyChRhPair
or validChRhPair
) is not applied by it, so
they must be applied further during the usage. Examples of the usage:
"c114+112=2" returns Just
P1 (Ch 1 1 4) (Rhythm 1 1 2) 2
"Mtttff7+112111=7*3" returns Just
P2 (PolyCh [True,True,True,False,False] 7) (PolyRhythm [1,1,2,1,1,1]) 7 3
.