phonetic-languages-phonetics-basics-0.3.0.0: A library for working with generalized phonetic languages usage.
Copyright(c) OleksandrZhabenko 2020-2021
LicenseMIT
Maintainerolexandr543@yahoo.com
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010
ExtensionsBangPatterns

Data.Phonetic.Languages.Syllables

Description

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

Synopsis

Documentation

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.

Instances

Instances details
Eq PRS Source # 
Instance details

Defined in Data.Phonetic.Languages.Syllables

Methods

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

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

Ord PRS Source # 
Instance details

Defined in Data.Phonetic.Languages.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 #

type CharPhoneticClassification = [PRS] Source #

The list 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.

isVowel1 :: PRS -> Bool Source #

Function-predicate isVowel1 checks whether its argument is a vowel representation in the PRS format.

isVwl :: Char -> Bool Source #

Function-predicate isVwl checks whether its argument is a vowel representation in the Char format.

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.

isNotVowel2 :: PRS -> PRS -> Bool Source #

Binary function-predicate isNotVowel2 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).

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 #

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 SegmentationRules1 Source #

Constructors

SP1 

Fields

type SegmentPredicates = [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.

divCnsnts :: [(Char, Char)] -> SegmentPredicates -> [PRS] -> ([PRS] -> [PRS], [PRS] -> [PRS]) Source #

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

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

createSyllablesPL Source #

Arguments

:: GWritingSystemPRPLX 
-> [(Char, Char)] 
-> CharPhoneticClassification 
-> SegmentPredicates 
-> String

Corresponds to the '0' symbol delimiter in the ukrainian-phonetics-basic-array package.

-> String

Corresponds to the '1' and '-' symbol delimiters in the ukrainian-phonetics-basic-array package.

-> String

Actually the converted String.

-> [[[PRS]]]