phonetic-languages-phonetics-basics-0.10.0.2: A library for working with generalized phonetic languages usage.
Copyright(c) Oleksandr Zhabenko 2021-2023
LicenseMIT
Maintaineroleksandr.zhabenko@yahoo.com
StabilityExperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • UnboxedTuples
  • BangPatterns
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash

Phladiprelio.General.Syllables

Description

This module works with syllable segmentation. The generalized version for the module Syllable from ukrainian-phonetics-basic-array package.

Synopsis

Data types and type synonyms

data PRS Source #

Constructors

SylS 

Fields

  • charS :: !Char

    Phonetic languages phenomenon representation. Usually, a phoneme, but it can be otherwise something different.

  • phoneType :: !PhoneticType

    Some encoded type. For the vowels it has reserved value of P 0, for the sonorous consonants - P 1 and P 2, for the voiced consonants - P 3 and P 4, for the voiceless consonants - P 5 and P 6. Nevertheless, it is possible to redefine the data by rewriting the respective parts of the code here.

Instances

Instances details
Read PRS Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Show PRS Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Methods

showsPrec :: Int -> PRS -> ShowS #

show :: PRS -> String #

showList :: [PRS] -> ShowS #

Eq PRS Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Methods

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

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

Ord PRS Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Methods

compare :: PRS -> PRS -> Ordering #

(<) :: PRS -> PRS -> Bool #

(<=) :: PRS -> PRS -> Bool #

(>) :: PRS -> PRS -> Bool #

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

max :: PRS -> PRS -> PRS #

min :: PRS -> PRS -> PRS #

DListRepresentation PRS Int8 Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Methods

toDLR :: Int8 -> [PRS] -> ([PRS] -> [PRS], [PRS] -> [PRS]) Source #

Eval2Bool (SegmentationPredFData PRS (Char, Char)) Source # 
Instance details

Defined in Phladiprelio.General.Syllables

type CharPhoneticClassification = Array Int PRS Source #

The Array Int must be sorted in the ascending order to be used in the module correctly.

type StringRepresentation = [PRS] Source #

The String of converted phonetic language representation Char data is converted to this type to apply syllable segmentation or other transformations.

data SegmentationInfo1 Source #

Constructors

SI 

Fields

  • fieldN :: !Int8

    Number of fields in the pattern matching that are needed to apply the segmentation rules. Not less than 1.

  • predicateN :: Int8

    Number of predicates in the definition for the fieldN that are needed to apply the segmentation rules.

data SegmentationPredFunction Source #

We can think of SegmentationPredFunction in terms of f (SI fN pN) ks [x_{1},x_{2},...,x_{i},...,x_{fN}]. Comparing with divCnsnts from the ukrainian-phonetics-basics-array we can postulate that it consists of the following logical terms in the symbolic form:

1) phoneType x_{i} `elem` (X{...} = map P [Int8])

2) notEqC ks x_{i} x_{j} (j /= i)

combined with the standard logic Boolean operations of (&&), (||) and not. Further, the not can be transformed into the positive (affirmative) form using the notion of the universal set for the task. This transformation needs that the similar phonetic phenomenae (e. g. the double sounds -- the prolonged ones) belong to the one syllable and not to the different ones (so they are not related to different syllables, but just to the one and the same). Since such assumption has been used, we can further represent the function by the following data type and operations with it, see SegmentationPredFData.

Constructors

PF (SegmentationInfo1 -> [(Char, Char)] -> [PRS] -> Bool) 

class Eval2Bool a where Source #

Methods

eval2Bool :: a -> Bool Source #

Instances

Instances details
Eval2Bool (SegmentationPredFData PRS (Char, Char)) Source # 
Instance details

Defined in Phladiprelio.General.Syllables

type DListFunctionResult = ([PRS] -> [PRS], [PRS] -> [PRS]) Source #

data SegmentationLineFunction Source #

Constructors

LFS 

Fields

data SegmentationRules1 Source #

Constructors

SR1 

Fields

type SegmentRulesG = [SegmentationRules1] Source #

List of the SegmentationRules1 sorted in the descending order by the fieldN SegmentationInfo1 data and where the length of all the SegmentationPredFunction lists of PRS are equal to the fieldN SegmentationInfo1 data by definition.

class DListRepresentation a b where Source #

Methods

toDLR :: b -> [a] -> ([a] -> [a], [a] -> [a]) Source #

Instances

Instances details
DListRepresentation PRS Int8 Source # 
Instance details

Defined in Phladiprelio.General.Syllables

Methods

toDLR :: Int8 -> [PRS] -> ([PRS] -> [PRS], [PRS] -> [PRS]) Source #

Basic functions

sndGroups :: [PRS] -> [[PRS]] Source #

Function sndGroups converts a word being a list of PRS to the list of phonetically similar (consonants grouped with consonants and each vowel separately) sounds representations in PRS format.

groupSnds :: [PRS] -> [[PRS]] Source #

divCnsnts Source #

Arguments

:: [(Char, Char)]

The pairs of the Char that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly.

-> SegmentRulesG 
-> [PRS] 
-> DListFunctionResult 

Function divCnsnts is used to divide groups of consonants into two-elements lists that later are made belonging to different neighbour syllables if the group is between two vowels in a word. The group must be not empty, but this is not checked. The example phonetical information for the proper performance in Ukrainian can be found from the: https://msn.khnu.km.ua/pluginfile.php/302375/mod_resource/content/1/%D0%9B.3.%D0%86%D0%86.%20%D0%A1%D0%BA%D0%BB%D0%B0%D0%B4.%D0%9D%D0%B0%D0%B3%D0%BE%D0%BB%D0%BE%D1%81.pdf The example of the divCnsnts can be found at: https://hackage.haskell.org/package/ukrainian-phonetics-basic-array-0.1.2.0/docs/src/Languages.Phonetic.Ukrainian.Syllable.Arr.html#divCnsnts

reSyllableCntnts Source #

Arguments

:: [(Char, Char)]

The pairs of the Char that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly.

-> SegmentRulesG 
-> [[PRS]] 
-> [[PRS]] 

divSylls :: [[PRS]] -> [[PRS]] Source #

createSyllablesPL Source #

Arguments

:: GWritingSystemPRPLX

Data used to obtain the phonetic language representation of the text.

-> [(Char, Char)]

The pairs of the Char that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly.

-> CharPhoneticClassification 
-> SegmentRulesG 
-> String

Corresponds to the 100 delimiter in the ukrainian-phonetics-basic-array package.

-> String

Corresponds to the 101 delimiter in the ukrainian-phonetics-basic-array package.

-> String

Actually the converted String.

-> [[[PRS]]] 

The function actually creates syllables using the provided data. Each resulting inner-most list is a phonetic language representation of the syllable according to the rules provided.

Auxiliary functions

gBF4 :: Ix i => (# Int#, PRS #) -> (# Int#, PRS #) -> Char -> Array i PRS -> Maybe PRS Source #

Is somewhat rewritten from the gBF3 function (not exported) from the mmsyn2-array package.

createsSyllable :: PRS -> Bool Source #

Function-predicate createsSyllable checks whether its argument is a phoneme representation that every time being presented in the text leads to the creation of the new syllable (in the PRS format). Usually it is a vowel, but in some languages there can be syllabic phonemes that are not considered to be vowels.

isSonorous1 :: PRS -> Bool Source #

Function-predicate isSonorous1 checks whether its argument is a sonorous consonant representation in the PRS format.

isVoicedC1 :: PRS -> Bool Source #

Function-predicate isVoicedC1 checks whether its argument is a voiced consonant representation in the PRS format.

isVoicelessC1 :: PRS -> Bool Source #

Function-predicate isVoiceless1 checks whether its argument is a voiceless consonant representation in the PRS format.

notCreatesSyllable2 :: PRS -> PRS -> Bool Source #

Binary function-predicate notCreatesSyllable2 checks whether its arguments are both consonant representations in the PRS format.

notEqC Source #

Arguments

:: [(Char, Char)]

The pairs of the Char that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly.

-> PRS 
-> PRS 
-> Bool 

Binary function-predicate notEqC checks whether its arguments are not the same consonant sound representations (not taking palatalization into account).