{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude, BangPatterns #-}

-- |
-- Module      :  Phladiprelio.Ukrainian.Syllable
-- Copyright   :  (c) Oleksandr Zhabenko 2021-2023
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- This module works with syllable segmentation in Ukrainian. It is rewritten
-- module MMSyn7.Syllable from the @mmsyn7s@ package : https://hackage.haskell.org/package/mmsyn7s
-- The information on Ukrainian syllable segmentation is taken 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
--

module Phladiprelio.Ukrainian.Syllable (
  -- * Basic functionality
  isVowel1
  , isSonorous1
  , isVoicedC1
  , isVoicelessC1
  , isNotVowel2
  , isNotVowel2'
  , sndGroups
  , groupSnds
  , divCnsnts
  , reSyllableCntnts
  , divVwls
  , createSyllablesUkrS
  , notEqC
  , representProlonged
  , showS8
  , showFS
  -- * With additional data used (probably for speed up)
  , notEqCTup
  , divCnsntsTup
  , reSyllableCntntsTup
  , createSyllablesUkrSTup
) where

import GHC.Base
import GHC.List
import Data.Tuple 
import GHC.Num (abs,(-))
import GHC.Arr
import Data.Typeable
import qualified Data.List as L (groupBy)
import Phladiprelio.Ukrainian.Melodics
import CaseBi.Arr
import GHC.Int
import Data.List.InnToOut.Basic (mapI)
import Data.Maybe (mapMaybe)


-- Inspired by: https://github.com/OleksandrZhabenko/mm1/releases/tag/0.2.0.0

-- | Function-predicate 'isVowel1' checks whether its argument is a vowel representation in the 'Sound8' format.
isVowel1 :: Sound8 -> Bool
isVowel1 :: Sound8 -> Bool
isVowel1 Sound8
x = Sound8
x forall a. Ord a => a -> a -> Bool
< Sound8
7
{-# INLINE isVowel1 #-}

-- | Function-predicate 'isSonorous1' checks whether its argument is a sonorous consonant representation in the 'Sound8' format.
isSonorous1 :: Sound8 -> Bool
isSonorous1 :: Sound8 -> Bool
isSonorous1 Sound8
x = Sound8
x forall a. Ord a => a -> a -> Bool
> Sound8
26 Bool -> Bool -> Bool
&& Sound8
x forall a. Ord a => a -> a -> Bool
< Sound8
38
{-# INLINE isSonorous1 #-}

-- | Function-predicate 'isVoicedC1' checks whether its argument is a voiced consonant representation in the 'Sound8' format.
isVoicedC1 :: Sound8 -> Bool
isVoicedC1 :: Sound8 -> Bool
isVoicedC1 Sound8
x = Sound8
x forall a. Ord a => a -> a -> Bool
> Sound8
7 Bool -> Bool -> Bool
&& Sound8
x forall a. Ord a => a -> a -> Bool
< Sound8
27
{-# INLINE isVoicedC1 #-}

-- | Function-predicate 'isVoiceless1' checks whether its argument is a voiceless consonant representation in the 'Sound8' format.
isVoicelessC1 :: Sound8 -> Bool
isVoicelessC1 :: Sound8 -> Bool
isVoicelessC1 Sound8
x = Sound8
x forall a. Ord a => a -> a -> Bool
> Sound8
37 Bool -> Bool -> Bool
&& Sound8
x forall a. Ord a => a -> a -> Bool
< Sound8
54
{-# INLINE isVoicelessC1 #-}

-- | Binary function-predicate 'isNotVowel2' checks whether its arguments are both consonant representations in the 'Sound8' format.
-- Starting from the version 0.6.0.0 variants of either of arguments is greater than 99 is also included.
isNotVowel2 :: Sound8 -> Sound8 -> Bool
isNotVowel2 :: Sound8 -> Sound8 -> Bool
isNotVowel2 Sound8
x Sound8
y = Sound8
x forall a. Ord a => a -> a -> Bool
> Sound8
6 Bool -> Bool -> Bool
&& Sound8
y forall a. Ord a => a -> a -> Bool
> Sound8
6
{-# INLINE isNotVowel2 #-}

-- | Binary function-predicate 'isNotVowel2'' checks whether its arguments are both consonant representations in the 'Sound8' format.
-- Starting from the version 0.6.0.0 variants of either of arguments is greater than 99 are not included (so its behaviour is equivalent  to the
-- 'isNotVowel2' till the 0.5.3.0 version).
isNotVowel2' :: Sound8 -> Sound8 -> Bool
isNotVowel2' :: Sound8 -> Sound8 -> Bool
isNotVowel2' Sound8
x Sound8
y = Sound8
x forall a. Ord a => a -> a -> Bool
< Sound8
100 Bool -> Bool -> Bool
&& Sound8
y forall a. Ord a => a -> a -> Bool
< Sound8
100 Bool -> Bool -> Bool
&& Sound8
x forall a. Ord a => a -> a -> Bool
> Sound8
6 Bool -> Bool -> Bool
&& Sound8
y forall a. Ord a => a -> a -> Bool
> Sound8
6
{-# INLINE isNotVowel2' #-}

-- | Function 'sndGroups' converts a Ukrainian word being a list of 'Sound8' to the list of phonetically similar (consonants grouped with consonants and each vowel separately)
-- sounds representations in 'Sound8' format.
sndGroups :: FlowSound -> [FlowSound]
sndGroups :: FlowSound -> [FlowSound]
sndGroups ys :: FlowSound
ys@(Sound8
_:FlowSound
_) = forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy Sound8 -> Sound8 -> Bool
isNotVowel2 FlowSound
ys
sndGroups FlowSound
_ = []

groupSnds :: FlowSound -> [FlowSound]
groupSnds :: FlowSound -> [FlowSound]
groupSnds = forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy (\Sound8
x Sound8
y -> Sound8 -> Bool
isVowel1 Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8 -> Bool
isVowel1 Sound8
y)

-- | Function 'divCnsnts' is used to divide groups of Ukrainian 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 phonetical information for the proper performance is taken 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
divCnsnts :: FlowSound -> (FlowSound -> FlowSound,FlowSound -> FlowSound)
divCnsnts :: FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsnts xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:zs :: FlowSound
zs@(Sound8
z:ts :: FlowSound
ts@(Sound8
_:FlowSound
_))))
  | Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
|| Sound8 -> Bool
isVoicedC1 Sound8
x =
      case Sound8
y of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "рибаль-ство"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y =
      case Sound8
z of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ts) -- "рокль-ський" (?), "супрасль-ський"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "дофр-ський" (?)
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsnts xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:zs :: FlowSound
zs@(Sound8
z:FlowSound
ts)))
  | Sound8 -> Bool
isSonorous1 Sound8
x =
      case Sound8
y of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "поль-ка", "каль-ка"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y =
      case Sound8
z of
        Sound8
7 -> (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs) -- "сього-дні"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs)
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsnts xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:FlowSound
zs))
  | (Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
&& Sound8 -> Sound8 -> Bool
notEqC Sound8
x Sound8
y Bool -> Bool -> Bool
&& Sound8
y forall a. Eq a => a -> a -> Bool
/= Sound8
7) Bool -> Bool -> Bool
|| (Sound8 -> Bool
isVoicedC1 Sound8
x Bool -> Bool -> Bool
&& Sound8 -> Bool
isVoicelessC1 Sound8
y) = ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsnts FlowSound
xs = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)

-- | Function 'divCnsntsTup' is a variant of the 'divCnsts' where you can provide the tuple element for 'getBFst'' inside.
divCnsntsTup :: Array Int (Int8,Bool) -> FlowSound -> (FlowSound -> FlowSound,FlowSound -> FlowSound)
divCnsntsTup :: Array Int (Sound8, Bool)
-> FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsntsTup !Array Int (Sound8, Bool)
tup17 xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:zs :: FlowSound
zs@(Sound8
z:ts :: FlowSound
ts@(Sound8
_:FlowSound
_))))
  | Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
|| Sound8 -> Bool
isVoicedC1 Sound8
x =
      case Sound8
y of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "рибаль-ство"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y =
      case Sound8
z of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ts) -- "рокль-ський" (?), "супрасль-ський"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "дофр-ський" (?)
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsntsTup !Array Int (Sound8, Bool)
tup17 xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:zs :: FlowSound
zs@(Sound8
z:FlowSound
ts)))
  | Sound8 -> Bool
isSonorous1 Sound8
x =
      case Sound8
y of
        Sound8
7 -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
7]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs) -- "поль-ка", "каль-ка"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y =
      case Sound8
z of
        Sound8
7 -> (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs) -- "сього-дні"
        Sound8
_ -> ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),forall a. Monoid a => a -> a -> a
mappend FlowSound
zs)  
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsntsTup !Array Int (Sound8, Bool)
tup17 xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:FlowSound
_))
  | (Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
&& (Array Int (Sound8, Bool) -> Sound8 -> Sound8 -> Bool
notEqCTup Array Int (Sound8, Bool)
tup17 Sound8
x Sound8
y) Bool -> Bool -> Bool
&& Sound8
y forall a. Eq a => a -> a -> Bool
/= Sound8
7) Bool -> Bool -> Bool
|| (Sound8 -> Bool
isVoicedC1 Sound8
x Bool -> Bool -> Bool
&& Sound8 -> Bool
isVoicelessC1 Sound8
y) = ((forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsntsTup Array Int (Sound8, Bool)
_ FlowSound
xs = (forall a. a -> a
id,forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)

reSyllableCntntsTup :: Array Int (Int8,Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup :: Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup !Array Int (Sound8, Bool)
tup17 (FlowSound
xs:FlowSound
ys:FlowSound
zs:[FlowSound]
xss)
  | (forall a. Ord a => a -> a -> Bool
> Sound8
6) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last forall a b. (a -> b) -> a -> b
$ FlowSound
ys = forall a b. (a, b) -> a
fst (Array Int (Sound8, Bool)
-> FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsntsTup Array Int (Sound8, Bool)
tup17 FlowSound
ys) FlowSound
xsforall a. a -> [a] -> [a]
:Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 (forall a b. (a, b) -> b
snd (Array Int (Sound8, Bool)
-> FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsntsTup Array Int (Sound8, Bool)
tup17 FlowSound
ys) FlowSound
zsforall a. a -> [a] -> [a]
:[FlowSound]
xss)
  | Bool
otherwise = Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 ((FlowSound
xs forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys)forall a. a -> [a] -> [a]
:FlowSound
zsforall a. a -> [a] -> [a]
:[FlowSound]
xss)
reSyllableCntntsTup !Array Int (Sound8, Bool)
tup17 (FlowSound
xs:FlowSound
ys:[FlowSound]
_) = [FlowSound
xs forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys]
reSyllableCntntsTup !Array Int (Sound8, Bool)
tup17 [FlowSound]
xss = [FlowSound]
xss

reSyllableCntnts :: [FlowSound] -> [FlowSound]
reSyllableCntnts :: [FlowSound] -> [FlowSound]
reSyllableCntnts (FlowSound
xs:FlowSound
ys:FlowSound
zs:[FlowSound]
xss)
  | (forall a. Ord a => a -> a -> Bool
> Sound8
6) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last forall a b. (a -> b) -> a -> b
$ FlowSound
ys = forall a b. (a, b) -> a
fst (FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsnts FlowSound
ys) FlowSound
xsforall a. a -> [a] -> [a]
:[FlowSound] -> [FlowSound]
reSyllableCntnts (forall a b. (a, b) -> b
snd (FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsnts FlowSound
ys) FlowSound
zsforall a. a -> [a] -> [a]
:[FlowSound]
xss)
  | Bool
otherwise = [FlowSound] -> [FlowSound]
reSyllableCntnts ((FlowSound
xs forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys)forall a. a -> [a] -> [a]
:FlowSound
zsforall a. a -> [a] -> [a]
:[FlowSound]
xss)
reSyllableCntnts (FlowSound
xs:FlowSound
ys:[FlowSound]
_) = [FlowSound
xs forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys]
reSyllableCntnts [FlowSound]
xss = [FlowSound]
xss

divVwls :: [FlowSound] -> [FlowSound]
divVwls :: [FlowSound] -> [FlowSound]
divVwls = forall a. (a -> Bool) -> (a -> [a]) -> [a] -> [a]
mapI (\FlowSound
ws -> (forall a. [a] -> Int
length forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter Sound8 -> Bool
isVowel1 forall a b. (a -> b) -> a -> b
$ FlowSound
ws) forall a. Ord a => a -> a -> Bool
> Int
1) FlowSound -> [FlowSound]
h3
  where h3 :: FlowSound -> [FlowSound]
h3 FlowSound
us = [FlowSound
ys forall a. Monoid a => a -> a -> a
`mappend` forall a. Int -> [a] -> [a]
take Int
1 FlowSound
zs] forall a. Monoid a => a -> a -> a
`mappend` (forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy (\Sound8
x Sound8
y -> Sound8 -> Bool
isVowel1 Sound8
x Bool -> Bool -> Bool
&& Sound8
y forall a. Ord a => a -> a -> Bool
> Sound8
6) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
1 forall a b. (a -> b) -> a -> b
$ FlowSound
zs)
                  where (FlowSound
ys,FlowSound
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Ord a => a -> a -> Bool
>Sound8
6) FlowSound
us

createSyllablesUkrS :: String -> [[FlowSound]]
createSyllablesUkrS :: String -> [[FlowSound]]
createSyllablesUkrS = forall a b. (a -> b) -> [a] -> [b]
map ([FlowSound] -> [FlowSound]
divVwls forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FlowSound] -> [FlowSound]
reSyllableCntnts forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
groupSnds) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
words1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FlowSound
convertToProperUkrainianI8
{-# INLINE createSyllablesUkrS #-}

createSyllablesUkrSTup
 :: Array Int (Int8, Bool)
     -> Array Int (Int8, Bool)
     -> Array Int (Int8, Bool)
     -> Array Int (Int8, Bool)
     -> Array Int ([Int8], Bool)
     -> Array Int ([Int8], Int8)
     -> Array Int (Int8, FlowSound -> Sound8)
     -> Array Int (Int8, Bool)
     -> Array Int ([Int8], Bool)
     -> Array Int ([Int8], Bool)
     -> Array Int ([Int8], Bool)
     -> Array Int (Int8, [Int8])
     -> Array Int (Char,Int8)
     -> Array Int (Int8,[Int8])
     -> Array Int (Char, Bool)
     -> Array Int (Char, Bool)
     -> Array Int (Int8,Bool)
     -> String
     -> [[FlowSound]]
createSyllablesUkrSTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Sound8)
-> Array Int (Sound8, FlowSound -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (Sound8, FlowSound)
-> Array Int (Char, Sound8)
-> Array Int (Sound8, FlowSound)
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[FlowSound]]
createSyllablesUkrSTup !Array Int (Sound8, Bool)
tup1 !Array Int (Sound8, Bool)
tup2 !Array Int (Sound8, Bool)
tup3 !Array Int (Sound8, Bool)
tup4 !Array Int (FlowSound, Bool)
tup5 !Array Int (FlowSound, Sound8)
tup6 !Array Int (Sound8, FlowSound -> Sound8)
tup7 !Array Int (Sound8, Bool)
tup8 !Array Int (FlowSound, Bool)
tup9 !Array Int (FlowSound, Bool)
tup10 !Array Int (FlowSound, Bool)
tup11 !Array Int (Sound8, FlowSound)
tup12 !Array Int (Char, Sound8)
tup13 !Array Int (Sound8, FlowSound)
tup14 !Array Int (Char, Bool)
tup15 !Array Int (Char, Bool)
tup16 !Array Int (Sound8, Bool)
tup17 =
 forall a b. (a -> b) -> [a] -> [b]
map ([FlowSound] -> [FlowSound]
divVwls forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
groupSnds) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
words1 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Sound8)
-> Array Int (Sound8, FlowSound -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (FlowSound, Bool)
-> Array Int (Sound8, FlowSound)
-> Array Int (Char, Sound8)
-> Array Int (Sound8, FlowSound)
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> String
-> FlowSound
convertToProperUkrainianI8WithTuples Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int (FlowSound, Bool)
tup5 Array Int (FlowSound, Sound8)
tup6 Array Int (Sound8, FlowSound -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int (FlowSound, Bool)
tup9 Array Int (FlowSound, Bool)
tup10 Array Int (FlowSound, Bool)
tup11 Array Int (Sound8, FlowSound)
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, FlowSound)
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16
{-# INLINE createSyllablesUkrSTup #-}

-- | Practically this is an optimized version for this case 'words' function from Prelude.
words1 :: FlowSound -> [FlowSound]
words1 :: FlowSound -> [FlowSound]
words1 FlowSound
xs = if forall a. [a] -> Bool
null FlowSound
ts then [] else FlowSound
w forall a. a -> [a] -> [a]
: FlowSound -> [FlowSound]
words1 FlowSound
s'' 
  where ts :: FlowSound
ts = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Ord a => a -> a -> Bool
> Sound8
99) FlowSound
xs
        (FlowSound
w, FlowSound
s'') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Ord a => a -> a -> Bool
< Sound8
100) FlowSound
ts
{-# NOINLINE words1 #-}

-----------------------------------------------------

-- | Binary function-predicate 'notEqC' checks whether its arguments are not the same consonant sound representations (not taking palatalization into account).
notEqC :: Sound8 -> Sound8 -> Bool
notEqC :: Sound8 -> Sound8 -> Bool
notEqC Sound8
x Sound8
y
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
49 Bool -> Bool -> Bool
|| Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
54 =
      case Sound8
y of
        Sound8
49 -> Bool
False
        Sound8
54 -> Bool
False
        Sound8
_   -> Bool
True
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
66 Bool -> Bool -> Bool
|| Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
38 =
      case Sound8
y of
        Sound8
38 -> Bool
False
        Sound8
66 -> Bool
False
        Sound8
_   -> Bool
True
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
y = Bool
False
  | forall a. Num a => a -> a
abs (Sound8
x forall a. Num a => a -> a -> a
- Sound8
y) forall a. Eq a => a -> a -> Bool
== Sound8
1 =
      forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstLSorted' Bool
True ([(Sound8
8,Bool
False),(Sound8
10,Bool
False),(Sound8
15,Bool
False),(Sound8
17,Bool
False),(Sound8
19,Bool
False),(Sound8
21,Bool
False),(Sound8
23,Bool
False),(Sound8
25,Bool
False),
         (Sound8
28,Bool
False),(Sound8
30,Bool
False),(Sound8
32,Bool
False),(Sound8
34,Bool
False),(Sound8
36,Bool
False),(Sound8
39,Bool
False),(Sound8
41,Bool
False),(Sound8
43,Bool
False),(Sound8
45,Bool
False),(Sound8
47,Bool
False),
           (Sound8
50,Bool
False),(Sound8
52,Bool
False)]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> a
min Sound8
x forall a b. (a -> b) -> a -> b
$ Sound8
y
  | Bool
otherwise = Bool
True

-- | Binary function-predicate 'notEqC' checks whether its arguments are not the same consonant sound representations (not taking palatalization into account).
notEqCTup :: Array Int (Int8,Bool) -> Sound8 -> Sound8 -> Bool
notEqCTup :: Array Int (Sound8, Bool) -> Sound8 -> Sound8 -> Bool
notEqCTup !Array Int (Sound8, Bool)
tup17 Sound8
x Sound8
y
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
49 Bool -> Bool -> Bool
|| Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
54 =
      case Sound8
y of
        Sound8
49 -> Bool
False
        Sound8
54 -> Bool
False
        Sound8
_   -> Bool
True
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
66 Bool -> Bool -> Bool
|| Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
38 =
      case Sound8
y of
        Sound8
38 -> Bool
False
        Sound8
66 -> Bool
False
        Sound8
_   -> Bool
True
  | Sound8
x forall a. Eq a => a -> a -> Bool
== Sound8
y = Bool
False
  | forall a. Num a => a -> a
abs (Sound8
x forall a. Num a => a -> a -> a
- Sound8
y) forall a. Eq a => a -> a -> Bool
== Sound8
1 = forall a b. Ord a => (b, Array Int (a, b)) -> a -> b
getBFst' (Bool
True, Array Int (Sound8, Bool)
tup17) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> a
min Sound8
x forall a b. (a -> b) -> a -> b
$ Sound8
y
  | Bool
otherwise = Bool
True

-- | Function 'representProlonged' converts duplicated consequent in the syllable consonants
-- so that they are represented by just one 'Sound8'. After applying the function to the list of 'Sound8' being a syllable all groups of duplicated consequent consonants
-- in every syllable are represented with only one 'Sound8' respectively.
representProlonged :: FlowSound -> FlowSound
representProlonged :: FlowSound -> FlowSound
representProlonged (Sound8
x:Sound8
y:FlowSound
xs)
  | Sound8 -> Bool
isVowel1 Sound8
x = Sound8
xforall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged (Sound8
yforall a. a -> [a] -> [a]
:FlowSound
xs)
  | Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sound8 -> Sound8 -> Bool
notEqC Sound8
x forall a b. (a -> b) -> a -> b
$ Sound8
y = Sound8
yforall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged FlowSound
xs
  | Bool
otherwise = Sound8
xforall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged (Sound8
yforall a. a -> [a] -> [a]
:FlowSound
xs)
representProlonged FlowSound
xs = FlowSound
xs

showS8 :: Sound8 -> String
showS8 :: Sound8 -> String
showS8 = forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstLSorted' String
" " [(Sound8
1,String
"\1072"),(Sound8
2,String
"\1077"),(Sound8
3,String
"\1086"),(Sound8
4,String
"\1091"),(Sound8
5,String
"\1080"),(Sound8
6,String
"\1110"),(Sound8
7,String
"\1100"),(Sound8
8,String
"\1076\1079"),
  (Sound8
9,String
"\1076\1079"),(Sound8
10,String
"\1078"),(Sound8
11,String
"\1078"),(Sound8
15,String
"\1073"),(Sound8
16,String
"\1073"),(Sound8
17,String
"\1076"),(Sound8
18,String
"\1076"),(Sound8
19,String
"\1169"),(Sound8
20,String
"\1169"),
  (Sound8
21,String
"\1075"),(Sound8
22,String
"\1075"),(Sound8
23,String
"\1076\1078"),(Sound8
24,String
"\1076\1078"),(Sound8
25,String
"\1079"),(Sound8
26,String
"\1079"),(Sound8
27,String
"\1081"),(Sound8
28,String
"\1083"),(Sound8
29,String
"\1083"),
  (Sound8
30,String
"\1084"),(Sound8
31,String
"\1084"),(Sound8
32,String
"\1085"),(Sound8
33,String
"\1085"),(Sound8
34,String
"\1088"),(Sound8
35,String
"\1088"),(Sound8
36,String
"\1074"),(Sound8
37,String
"\1074"),(Sound8
38,String
"\1094"),
  (Sound8
39,String
"\1095"),(Sound8
40,String
"\1095"),(Sound8
41,String
"\1096"),(Sound8
42,String
"\1096"),(Sound8
43,String
"\1092"),(Sound8
44,String
"\1092"),(Sound8
45,String
"\1082"),(Sound8
46,String
"\1082"),(Sound8
47,String
"\1087"),
  (Sound8
48,String
"\1087"),(Sound8
49,String
"\1089"),(Sound8
50,String
"\1090"),(Sound8
51,String
"\1090"),(Sound8
52,String
"\1093"),(Sound8
53,String
"\1093"),(Sound8
54,String
"\1089\1100"),(Sound8
66,String
"\1094\1100")]
{-# INLINABLE showS8 #-}

showFS :: FlowSound -> String
showFS :: FlowSound -> String
showFS = forall a b. (a -> [b]) -> [a] -> [b]
concatMap Sound8 -> String
showS8  -- Probably, it is better to transform several consequent spaces into the combination smth like \", \" (but not in this version)
{-# INLINE showFS #-}