Copyright | (c) OleksandrZhabenko 2020-2022 |
---|---|
License | MIT |
Maintainer | olexandr543@yahoo.com |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
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])]
- generalProc3G :: PermutationsType -> (String -> Bool) -> [String] -> String -> Int -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> FilePath -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> Bool -> Int -> Int -> IO ()
- generalProc2G :: PermutationsType -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> FilePath -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> Bool -> Int -> Int -> IO ()
- generalProc2 :: PermutationsType -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> Bool -> Int -> Int -> IO (ReadyForConstructionPL, String)
- messageInfo :: Int -> String
- interactivePrintResult :: (a -> String) -> [a] -> Bool -> Int -> IO (ReadyForConstructionPL, String)
- interactivePrintResultRecursive :: PermutationsType -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> Bool -> Int -> Int -> IO (ReadyForConstructionPL, String)
- printWarning :: String -> IO String
- show2 :: (Show a1, Show a2, Num a3, Ord a1, Ord a2, Eq a3) => a3 -> [Result2 ReadyForConstructionPL a1 a2] -> String
- print2 :: (Show a1, Show a2, Num a3, Ord a1, Ord a2, Eq a3) => a3 -> [Result2 ReadyForConstructionPL a1 a2] -> IO ()
- generalProcMs :: GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> [MappingFunctionPL] -> Coeffs2 -> Coeffs2 -> [Array Int Int] -> [String] -> ([Int], String, Int, String) -> IO [Result2 ReadyForConstructionPL Double Double]
- generalProcMMs :: PermutationsType -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [([Int], String, Int, String)] -> [Array Int Int] -> [String] -> [String] -> Bool -> Bool -> Int -> Int -> IO (ReadyForConstructionPL, String)
- finalProc :: PermutationsType -> GWritingSystemPRPLX -> [(Char, Char)] -> CharPhoneticClassification -> SegmentRulesG -> String -> String -> (Double -> String -> MappingFunctionPL) -> [MappingFunctionPL] -> [MappingFunctionPL] -> Concatenations -> Concatenations -> String -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> Bool -> Int -> Int -> IO (ReadyForConstructionPL, String)
- print1el :: Bool -> String -> [Result2 ReadyForConstructionPL Double Double] -> IO (ReadyForConstructionPL, String)
Documentation
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> (String -> Bool) | The predicate that checks whether the given argument is not a phonetic language word in the representation. |
-> [String] | |
-> String | If empty, the function is just |
-> Int | |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> 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 | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | Whether to print more verbose information in the output with sorting in some way |
-> IO () |
Is used to organize the most complex processment -- for multiple sources and probably recursively.
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> 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 | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | |
-> IO () |
Is used to do general processment.
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> [MappingFunctionPL] | |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> 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 | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | |
-> IO (ReadyForConstructionPL, String) |
messageInfo :: Int -> String Source #
Function provides message information.
interactivePrintResult :: (a -> String) -> [a] -> Bool -> Int -> IO (ReadyForConstructionPL, String) Source #
interactivePrintResultRecursive Source #
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> [MappingFunctionPL] | |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> Bool | |
-> Bool | |
-> [String] | |
-> Coeffs2 | |
-> Coeffs2 | |
-> (a -> String) | |
-> [a] | |
-> [String] | |
-> Bool | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | |
-> IO (ReadyForConstructionPL, String) |
show2 :: (Show a1, Show a2, Num a3, Ord a1, Ord a2, Eq a3) => a3 -> [Result2 ReadyForConstructionPL a1 a2] -> String Source #
print2 :: (Show a1, Show a2, Num a3, Ord a1, Ord a2, Eq a3) => a3 -> [Result2 ReadyForConstructionPL a1 a2] -> IO () Source #
:: 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> [MappingFunctionPL] | |
-> 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], String, Int, String) | The |
-> IO [Result2 ReadyForConstructionPL Double Double] |
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> [MappingFunctionPL] | |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> 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. |
-> [([Int], String, Int, String)] | The |
-> [Array Int Int] | Permutations data. |
-> [String] | |
-> [String] | |
-> Bool | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | |
-> IO (ReadyForConstructionPL, String) |
:: PermutationsType | Whether to use just one of the express permutations, or the full universal set. |
-> 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 -> MappingFunctionPL) | The function that is needed in the |
-> [MappingFunctionPL] | A list of |
-> [MappingFunctionPL] | |
-> Concatenations | Data used to concatenate (prepend) 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. |
-> Concatenations | Data used to concatenate (append) 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 | Whether to run in the recursive mode. |
-> Bool | |
-> Bool | |
-> [String] | |
-> Coeffs2 | |
-> Coeffs2 | |
-> (a -> String) | |
-> [a] | |
-> [String] | |
-> Bool | |
-> Bool | Whether to use volatile string weights |
-> Int | Number of sets of volatile string weights for every processed line. Is used when the previous one is |
-> Int | |
-> IO (ReadyForConstructionPL, String) |