Copyright | (c) Oleksandr Zhabenko 2022-2023 |
---|---|
License | MIT |
Maintainer | oleksandr.zhabenko@yahoo.com |
Stability | Experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions | BangPatterns |
Data and algorithmic basics to evaluate rhythmicity of the lists of Ord
instance data type.
Similar to phonetic-languages-rhythmicity
on Hackage.
Synopsis
- showBin :: Int -> [Char]
- unionCount :: Bits a => a -> a -> Integer
- countWeightsQs :: Foldable t => [t a -> Int] -> [t a] -> [[Int]]
- data Sort2 a = S2 {}
- data ASort3 a = As3 {}
- splitF :: Int -> [a] -> [[a]]
- getHashes2 :: Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
- countHashesPrioritized :: Bits b => [[b]] -> [[Integer]]
- count1Hashes :: Ord a => Int8 -> [Int8] -> [a] -> Integer
- data HashCorrections = H [Int8] Int8
- hashCorrections2F :: HashCorrections -> Int8 -> [Integer] -> Integer
- hashList :: HashCorrections -> [Int8]
- readHashCorrections :: String -> HashCorrections
- grouppingR :: String -> (Int8, [Int8])
- countHashesG :: Ord a => HashCorrections -> Int8 -> [Int8] -> [a] -> [Integer]
- countHashes2G :: Ord a => Int -> HashCorrections -> Int8 -> [Int8] -> [a] -> [Integer]
- createNewHash :: [Integer] -> Integer
- createHashG :: (Int8 -> [Integer] -> Integer) -> Int8 -> [Integer] -> Integer
- createHash2G :: Int -> HashCorrections -> Int8 -> [Integer] -> Integer
- createNHash :: [Int8] -> [Integer] -> Integer
- idList :: Eq a => [Int8] -> [ASort3 a] -> [Int8]
- toNum :: [Int8] -> Integer
- toNum2 :: [Int8] -> Integer
- showZerosFor2Period :: Ord a => [[a]] -> Int -> (b -> String) -> [[[b]]] -> (String, [Integer])
- showZerosFor2PeriodMusic :: [(String, Word8)] -> (String, [Integer])
Documentation
showBin :: Int -> [Char] Source #
The similar function is since base-4.16.0.0
in the Numeric
module. Is not used
further, is provided here mostly for testing purposes.
unionCount :: Bits a => a -> a -> Integer Source #
Basic counting of the same bits in the Bits
arguments.
countWeightsQs :: Foldable t => [t a -> Int] -> [t a] -> [[Int]] Source #
Some idea function to evaluate the rhythmicity data. Is not used further in the package, can be thought of as an alternative way of computation.
Data type used to provide somewhat 'array sorting with its indices'.
Data type to contain the needed for hashing algorithm information about the sorted 'array sorting with its indices'.
splitF :: Int -> [a] -> [[a]] Source #
Split the list into lists of n
elements where n
is the first parameter. Can be used
efficiently just for the finite lists. Contains the modified code of the unfoldr
function from the base
package.
:: Ord a | |
=> Int8 | A period of the groups (the length of the lists into which the general sequence is splitted at first). |
-> [Int8] | The list must be sorted in the descending order, the elements must be greater or equal to 0 and less than the first argument of |
-> [a] | A list of |
-> [[Integer]] |
Function to get basic data for hash-based evaluation of the rhythmicity of the list data. Is
used internally in the countHashesG
.
Provided here mostly for testing purposes.
countHashesPrioritized :: Bits b => [[b]] -> [[Integer]] Source #
Convert hashes into basic simler data to evaluate rhythmicity of the list data.
data HashCorrections Source #
Data type to encode the changes that are introduced by the position of the group
of values in general sequence to the general result of the createHashesG
function. If the second parameter in the HashCorrections
is 1 then the result is more
sensitive to beginning of the line; if it is set to 2 then the result is more sensitive
to ending of the line; if it is greater than 2 then the result is sensitive to some
user weights provided as the first parameter to HashCorrections
and otherwise
the computation result does not depend on the first parameter to HashCorrections
(this
one can be considered the basic option for the computation).
Instances
Show HashCorrections Source # | |
Defined in Rhythmicity.MarkerSeqs showsPrec :: Int -> HashCorrections -> ShowS # show :: HashCorrections -> String # showList :: [HashCorrections] -> ShowS # | |
Eq HashCorrections Source # | |
Defined in Rhythmicity.MarkerSeqs (==) :: HashCorrections -> HashCorrections -> Bool # (/=) :: HashCorrections -> HashCorrections -> Bool # |
hashCorrections2F :: HashCorrections -> Int8 -> [Integer] -> Integer Source #
hashList :: HashCorrections -> [Int8] Source #
If the second parameter in the HashCorrections
is 1 then the result is more
sensitive to beginning of the line; if it is set to 2 then the result is more sensitive
to ending of the line; if it is greater than 2 then the result is sensitive to some
user weights provided as the first parameter to HashCorrections
and otherwise
the computation result does not depend on the first parameter to HashCorrections
(this
one can be considered the basic option for the computation).
readHashCorrections :: String -> HashCorrections Source #
If you would like to specify just your own values then specify the Lexeme
"a..." where
'a' here means the minus sign '-' or some not equal to 1 or 2 digit,
instead of dots specify some digits that are the beginning of the [Int8
] list in
HashCorrections
. If 'a' is '-', then the next not equal to 'a' symbol should be
some digit not equal to 1 or 2 if you want to specify your own list of [Int8]
for
HashCorrections
.
Caution:
readHashCorrections . show $ xs /= xs
show . readHashCorrections $ xs /= xs
in general case. The default value is H [0,0..] 0
. This one corresponds to usage of the
hashBalancingLF2
without any corrections (equi-sensitive to all the parts of the line except
probably the last syllables if the number of syllables is not wholely divisible without remainder
to the groupLength parameter in the countHashesG
function). And this is equivalent to just
use the hashBasicLF2
.
grouppingR :: String -> (Int8, [Int8]) Source #
This is used to provide the second and the third arguments to countHashesG
function. The
default value is (4,[3,2])
. This means that the line is divided into groups of 4-syllables
then there are searched for rhythmic repetitions of the positions of the most maximum values
and the less maximum values. This scheme should is related to disyllables metrical feet for SaaW
(syllables-as-a-whole) mode of operation for PhLADiPreLiO (see:
https://oleksandrzhabenko.github.io/uk/rhythmicity/PhLADiPreLiO.Eng.21.html#SaaW).
For more information on the metrical feet you can see e. g.
@article{hyde2002restrictive, title={A restrictive theory of metrical stress}, author={Hyde, Brett}, journal={Phonology}, volume={19}, number={3}, pages={313--359}, year={2002}, publisher={Cambridge University Press} }
:: Ord a | |
=> HashCorrections | Data that specifies how the arguments influence the result. Somewhat the kernel of the |
-> Int8 | The period of the length of the initial list. |
-> [Int8] | List of ordinary positions of the maximum-minimum levels for values of the list in the group. The length of the unique elements together in the list is expected to be in the list [1..7]. |
-> [a] | |
-> [Integer] |
General implementation of the hash-based algorithm to evaluate the level of rhythmicity of the list data. The relatively greater result (for PhLADiPreLiO) corresponds to greater detected periodicity.
:: Ord a | |
=> Int | The first parameter for |
-> HashCorrections | Data that specifies how the arguments influence the result. Somewhat the kernel of the |
-> Int8 | The period of the length of the initial list. |
-> [Int8] | List of ordinary positions of the maximum-minimum levels for values of the list in the group. The length of the unique elements together in the list is expected to be in the list [1..7]. |
-> [a] | |
-> [Integer] |
General implementation of the hash-based algorithm to evaluate the level of rhythmicity of the list data. The relatively greater result (for PhLADiPreLiO) corresponds to greater detected periodicity.
createNewHash :: [Integer] -> Integer Source #
Provided for testing.
createHashG :: (Int8 -> [Integer] -> Integer) -> Int8 -> [Integer] -> Integer Source #
General implementation of the second hashing of the data for the algorithm.
createHash2G :: Int -> HashCorrections -> Int8 -> [Integer] -> Integer Source #
General implementation of the second hashing of the data for the algorithm with the additional
parameter that specifies the step of hashing (by default, e. g. in createHashG
it is equal to
20, but here you can provide your own value). Therefore, is more flexible than createHashG
, but
can lead to not well coordinated evaluations in general case that wipe by hashing some
information in the data. Is intended that the first argument is greater than 2 though it is not
checked.
createNHash :: [Int8] -> [Integer] -> Integer Source #
A variant of the createHashG
that actually must be equal to the createNewHash
for the
second argument lists
with less than 8 elements. For greater values is not correctly defined, so do not use it for
the lists with 8 or more elements in them. Actually should be equal to createNewHash
for the
second argument.
idList :: Eq a => [Int8] -> [ASort3 a] -> [Int8] Source #
Function to filter the elements by the second parameter of the ASort3
data
and then to get the first ones.
toNum :: [Int8] -> Integer Source #
Function to create bitwise representation of the intermediate data for the algorithm. Should be very optimized to run fast.
toNum2 :: [Int8] -> Integer Source #
The alternative implementation of the toNum
(on the Linux x86_64 for some CPU is
slower than the former one).
showZerosFor2Period :: Ord a => [[a]] -> Int -> (b -> String) -> [[[b]]] -> (String, [Integer]) Source #
Function for generating the information to be used for evaluation of the points of the uncongruencies' influences on the pauses in the case of the period of the line is equal to 2 (two-syllable meter). See for the theoretical idea the paper by the link: https://www.academia.edu/105067761/Why_some_lines_are_easy_to_pronounce_and_others_are_not_or_prosodic_unpredictability_as_a_characteristic_of_text (English text) https://www.academia.edu/105067723/%D0%A7%D0%BE%D0%BC%D1%83_%D0%B4%D0%B5%D1%8F%D0%BA%D1%96_%D1%80%D1%8F%D0%B4%D0%BA%D0%B8_%D0%BB%D0%B5%D0%B3%D0%BA%D0%BE_%D0%B2%D0%B8%D0%BC%D0%BE%D0%B2%D0%BB%D1%8F%D1%82%D0%B8_%D0%B0_%D1%96%D0%BD%D1%88%D1%96_%D0%BD%D1%96_%D0%B0%D0%B1%D0%BE_%D0%BF%D1%80%D0%BE%D1%81%D0%BE%D0%B4%D0%B8%D1%87%D0%BD%D0%B0_%D0%BD%D0%B5%D1%81%D0%BF%D1%80%D0%BE%D0%B3%D0%BD%D0%BE%D0%B7%D0%BE%D0%B2%D0%B0%D0%BD%D1%96%D1%81%D1%82%D1%8C_%D1%8F%D0%BA_%D1%85%D0%B0%D1%80%D0%B0%D0%BA%D1%82%D0%B5%D1%80%D0%B8%D1%81%D1%82%D0%B8%D0%BA%D0%B0_%D1%82%D0%B5%D0%BA%D1%81%D1%82%D1%83 (Ukrainian text)
showZerosFor2PeriodMusic :: [(String, Word8)] -> (String, [Integer]) Source #
Function for generating the information to be used for evaluation of the points of the uncongruencies' influences on the pauses in the case of the period of the line is equal to 2 (two-syllable meter). Anologue of the swohZerosFor2Period
but is intended to be used for the "music" mode of PhLADiPreLiO.
See for the theoretical idea the paper by the link:
https://www.academia.edu/105067761/Why_some_lines_are_easy_to_pronounce_and_others_are_not_or_prosodic_unpredictability_as_a_characteristic_of_text (English text)
https://www.academia.edu/105067723/%D0%A7%D0%BE%D0%BC%D1%83_%D0%B4%D0%B5%D1%8F%D0%BA%D1%96_%D1%80%D1%8F%D0%B4%D0%BA%D0%B8_%D0%BB%D0%B5%D0%B3%D0%BA%D0%BE_%D0%B2%D0%B8%D0%BC%D0%BE%D0%B2%D0%BB%D1%8F%D1%82%D0%B8_%D0%B0_%D1%96%D0%BD%D1%88%D1%96_%D0%BD%D1%96_%D0%B0%D0%B1%D0%BE_%D0%BF%D1%80%D0%BE%D1%81%D0%BE%D0%B4%D0%B8%D1%87%D0%BD%D0%B0_%D0%BD%D0%B5%D1%81%D0%BF%D1%80%D0%BE%D0%B3%D0%BD%D0%BE%D0%B7%D0%BE%D0%B2%D0%B0%D0%BD%D1%96%D1%81%D1%82%D1%8C_%D1%8F%D0%BA_%D1%85%D0%B0%D1%80%D0%B0%D0%BA%D1%82%D0%B5%D1%80%D0%B8%D1%81%D1%82%D0%B8%D0%BA%D0%B0_%D1%82%D0%B5%D0%BA%D1%81%D1%82%D1%83 (Ukrainian text)