Copyright | (c) OleksandrZhabenko 2020-2021 |
---|---|
License | MIT |
Maintainer | olexandr543@yahoo.com |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Extensions | BangPatterns |
Library module that contains functions earlier used by the lineVariantsG3
executable for the Ukrainian language (see: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array).
Is rewritten from the Phonetic.Languages.Simple module from the
phonetic-languages-simplified-examples-array
package.
Synopsis
- forMultiplePropertiesF :: [String] -> [(String, [String])]
- generalProc2G :: GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> [[[PRS]]] -> [[Double]]) -> [[[[PRS]]] -> [[Double]]] -> Concatenations -> String -> FilePath -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> IO ()
- generalProc2 :: GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> [[[PRS]]] -> [[Double]]) -> [[[[PRS]]] -> [[Double]]] -> Concatenations -> String -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> IO String
- messageInfo :: Int -> String
- interactivePrintResult :: (a -> String) -> [a] -> IO String
- printWarning :: String -> IO String
- generalProcMs :: GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> [[[PRS]]] -> [[Double]]) -> [[[[PRS]]] -> [[Double]]] -> Coeffs2 -> Coeffs2 -> [Array Int Int] -> [String] -> ([Int], Int, Int, String) -> IO [Result [] Char Double Double]
- generalProcMMs :: GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> [[[PRS]]] -> [[Double]]) -> [[[[PRS]]] -> [[Double]]] -> Bool -> Coeffs2 -> Coeffs2 -> [([Int], Int, Int, String)] -> [Array Int Int] -> [String] -> IO String
- foldlI :: [[String]] -> [String]
- finalProc :: Bool -> (a -> String) -> [a] -> IO String
- print1el :: Bool -> String -> [Result [] Char Double Double] -> IO String
Documentation
:: GWritingSystemPRPLX | Data used to obtain the phonetic language representation of the text. |
-> [(Char, Char)] | The pairs of the |
-> CharPhoneticClassification | The |
-> SegmentRulesG | |
-> String | |
-> String | |
-> (Double -> String -> [[[PRS]]] -> [[Double]]) | The function that is needed in the |
-> [[[[PRS]]] -> [[Double]]] | A list of 4 different functions that specifies the syllables durations, analogues of the
syllableDurationsD functions from the |
-> Concatenations | Data used to concatenate the basic grammar preserving words and word sequences to the next word to leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. |
-> String | |
-> FilePath | |
-> Bool | |
-> Bool | |
-> [String] | |
-> Coeffs2 | This value is used when property choice is NOT from the "w" or "x" lines. |
-> Coeffs2 | This value is used when property choice is from the "w" or "x" lines. |
-> [String] | |
-> Bool | |
-> IO () |
Is used to do general processment.
:: GWritingSystemPRPLX | Data used to obtain the phonetic language representation of the text. |
-> [(Char, Char)] | The pairs of the |
-> CharPhoneticClassification | The |
-> SegmentRulesG | |
-> String | |
-> String | |
-> (Double -> String -> [[[PRS]]] -> [[Double]]) | The function that is needed in the |
-> [[[[PRS]]] -> [[Double]]] | A list of 4 different functions that specifies the syllables durations, analogues of the
syllableDurationsD functions from the |
-> Concatenations | Data used to concatenate the basic grammar preserving words and word sequences to the next word to leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. |
-> String | |
-> Bool | |
-> Bool | |
-> [String] | |
-> Coeffs2 | This value is used when property choice is NOT from the "w" or "x" lines. |
-> Coeffs2 | This value is used when property choice is from the "w" or "x" lines. |
-> [String] | |
-> Bool | |
-> IO String |
messageInfo :: Int -> String Source #
Function provides message information.
:: GWritingSystemPRPLX | Data used to obtain the phonetic language representation of the text. |
-> [(Char, Char)] | The pairs of the |
-> CharPhoneticClassification | The |
-> SegmentRulesG | |
-> String | |
-> String | |
-> (Double -> String -> [[[PRS]]] -> [[Double]]) | The function that is needed in the |
-> [[[[PRS]]] -> [[Double]]] | A list of 4 different functions that specifies the syllables durations, analogues of the
syllableDurationsD functions from the |
-> Coeffs2 | This value is used when property choice is NOT from the "w" or "x" lines. |
-> Coeffs2 | This value is used when property choice is from the "w" or "x" lines. |
-> [Array Int Int] | Permutations data. |
-> [String] | |
-> ([Int], Int, Int, String) | The |
-> IO [Result [] Char Double Double] |
:: GWritingSystemPRPLX | Data used to obtain the phonetic language representation of the text. |
-> [(Char, Char)] | The pairs of the |
-> CharPhoneticClassification | The |
-> SegmentRulesG | |
-> String | |
-> String | |
-> (Double -> String -> [[[PRS]]] -> [[Double]]) | The function that is needed in the |
-> [[[[PRS]]] -> [[Double]]] | A list of 4 different functions that specifies the syllables durations, analogues of the
syllableDurationsD functions from the |
-> Bool | |
-> Coeffs2 | This value is used when property choice is NOT from the "w" or "x" lines. |
-> Coeffs2 | This value is used when property choice is from the "w" or "x" lines. |
-> [([Int], Int, Int, String)] | The |
-> [Array Int Int] | Permutations data. |
-> [String] | |
-> IO String |