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

-- |
-- Module      :  Languages.Phonetic.Ukrainian.Syllable.ArrInt8
-- Copyright   :  (c) OleksandrZhabenko 2021-2022
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@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 Languages.Phonetic.Ukrainian.Syllable.ArrInt8 (
  -- * Basic functionality
  isVowel1
  , isSonorous1
  , isVoicedC1
  , isVoicelessC1
  , isNotVowel2
  , sndGroups
  , groupSnds
  , divCnsnts
  , reSyllableCntnts
  , divVwls
  , createSyllablesUkrS
  , notEqC
  , representProlonged
  -- * With additional data used (probably for speed up)
  , notEqCTup
  , divCnsntsTup
  , reSyllableCntntsTup
  , createSyllablesUkrSTup
) where

import Prelude hiding (mappend)
import GHC.Arr
import Data.Monoid
import Data.Typeable
import qualified Data.List as L (groupBy)
import Melodics.Ukrainian.ArrInt8
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 Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
0 Bool -> Bool -> Bool
&& Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
26 Bool -> Bool -> Bool
&& Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
7 Bool -> Bool -> Bool
&& Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
37 Bool -> Bool -> Bool
&& Sound8
x Sound8 -> Sound8 -> Bool
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.
isNotVowel2 :: Sound8 -> Sound8 -> Bool
isNotVowel2 :: Sound8 -> Sound8 -> Bool
isNotVowel2 Sound8
x Sound8
y = Sound8
x Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
6 Bool -> Bool -> Bool
&& Sound8
y Sound8 -> Sound8 -> Bool
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
_) = (Sound8 -> Sound8 -> Bool) -> FlowSound -> [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 = (Sound8 -> Sound8 -> Bool) -> FlowSound -> [FlowSound]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy (\Sound8
x Sound8
y -> Sound8 -> Bool
isVowel1 Sound8
x Bool -> Bool -> Bool
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
_:Sound8
_:Sound8
_:FlowSound
_))
  | Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
|| Sound8 -> Bool
isVoicedC1 Sound8
x = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
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
_:FlowSound
_)))
  | Sound8 -> Bool
isSonorous1 Sound8
x = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
zs)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsnts xs :: FlowSound
xs@(Sound8
x:ys :: FlowSound
ys@(Sound8
y:FlowSound
_))
  | (Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
&& (Sound8 -> Sound8 -> Bool
notEqC Sound8
x Sound8
y)) Bool -> Bool -> Bool
|| (Sound8 -> Bool
isVoicedC1 Sound8
x Bool -> Bool -> Bool
&& Sound8 -> Bool
isVoicelessC1 Sound8
y) = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsnts FlowSound
xs = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
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
_:Sound8
_:Sound8
_:FlowSound
_))
  | Sound8 -> Bool
isSonorous1 Sound8
x Bool -> Bool -> Bool
|| Sound8 -> Bool
isVoicedC1 Sound8
x = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
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
_:FlowSound
_)))
  | Sound8 -> Bool
isSonorous1 Sound8
x = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Sound8 -> Bool
isSonorous1 Sound8
y = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x,Sound8
y]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
zs)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
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 -> Bool
isVoicedC1 Sound8
x Bool -> Bool -> Bool
&& Sound8 -> Bool
isVoicelessC1 Sound8
y) = ((FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` [Sound8
x]),FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
ys)
  | Bool
otherwise = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
mappend FlowSound
xs)
divCnsntsTup Array Int (Sound8, Bool)
_ FlowSound
xs = (FlowSound -> FlowSound
forall a. a -> a
id,FlowSound -> FlowSound -> FlowSound
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)
  | (Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
6) (Sound8 -> Bool) -> (FlowSound -> Sound8) -> FlowSound -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> Sound8
forall a. [a] -> a
last (FlowSound -> Bool) -> FlowSound -> Bool
forall a b. (a -> b) -> a -> b
$ FlowSound
ys = (FlowSound -> FlowSound, FlowSound -> FlowSound)
-> FlowSound -> FlowSound
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
xsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 ((FlowSound -> FlowSound, FlowSound -> FlowSound)
-> FlowSound -> FlowSound
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
zsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:[FlowSound]
xss)
  | Bool
otherwise = Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 ((FlowSound
xs FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys)FlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:FlowSound
zsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:[FlowSound]
xss)
reSyllableCntntsTup !Array Int (Sound8, Bool)
tup17 (FlowSound
xs:FlowSound
ys:[FlowSound]
_) = [FlowSound
xs FlowSound -> FlowSound -> FlowSound
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)
  | (Sound8 -> Sound8 -> Bool
forall a. Ord a => a -> a -> Bool
> Sound8
6) (Sound8 -> Bool) -> (FlowSound -> Sound8) -> FlowSound -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> Sound8
forall a. [a] -> a
last (FlowSound -> Bool) -> FlowSound -> Bool
forall a b. (a -> b) -> a -> b
$ FlowSound
ys = (FlowSound -> FlowSound, FlowSound -> FlowSound)
-> FlowSound -> FlowSound
forall a b. (a, b) -> a
fst (FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsnts FlowSound
ys) FlowSound
xsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:[FlowSound] -> [FlowSound]
reSyllableCntnts ((FlowSound -> FlowSound, FlowSound -> FlowSound)
-> FlowSound -> FlowSound
forall a b. (a, b) -> b
snd (FlowSound -> (FlowSound -> FlowSound, FlowSound -> FlowSound)
divCnsnts FlowSound
ys) FlowSound
zsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:[FlowSound]
xss)
  | Bool
otherwise = [FlowSound] -> [FlowSound]
reSyllableCntnts ((FlowSound
xs FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys)FlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:FlowSound
zsFlowSound -> [FlowSound] -> [FlowSound]
forall a. a -> [a] -> [a]
:[FlowSound]
xss)
reSyllableCntnts (FlowSound
xs:FlowSound
ys:[FlowSound]
_) = [FlowSound
xs FlowSound -> FlowSound -> FlowSound
forall a. Monoid a => a -> a -> a
`mappend` FlowSound
ys]
reSyllableCntnts [FlowSound]
xss = [FlowSound]
xss

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

createSyllablesUkrS :: String -> [[FlowSound]]
createSyllablesUkrS :: String -> [[FlowSound]]
createSyllablesUkrS = (FlowSound -> [FlowSound]) -> [FlowSound] -> [[FlowSound]]
forall a b. (a -> b) -> [a] -> [b]
map ([FlowSound] -> [FlowSound]
divVwls ([FlowSound] -> [FlowSound])
-> (FlowSound -> [FlowSound]) -> FlowSound -> [FlowSound]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FlowSound] -> [FlowSound]
reSyllableCntnts ([FlowSound] -> [FlowSound])
-> (FlowSound -> [FlowSound]) -> FlowSound -> [FlowSound]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
groupSnds) ([FlowSound] -> [[FlowSound]])
-> (String -> [FlowSound]) -> String -> [[FlowSound]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
forall a. (Ord a, Num a) => [a] -> [[a]]
words1 (FlowSound -> [FlowSound])
-> (String -> FlowSound) -> String -> [FlowSound]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FlowSound
convertToProperUkrainianI8 (String -> FlowSound) -> (String -> String) -> String -> FlowSound
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' then Char
' ' else Char
x)
    where words1 :: [a] -> [[a]]
words1 [a]
xs = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
ts then [] else [a]
w [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [[a]]
words1 [a]
s'' -- Practically this is an optimized version for this case 'words' function from Prelude.
             where ts :: [a]
ts = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1) [a]
xs
                   ([a]
w, [a]
s'') = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0) [a]
ts
          {-# NOINLINE words1 #-}
{-# 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 =
 (FlowSound -> [FlowSound]) -> [FlowSound] -> [[FlowSound]]
forall a b. (a -> b) -> [a] -> [b]
map ([FlowSound] -> [FlowSound]
divVwls ([FlowSound] -> [FlowSound])
-> (FlowSound -> [FlowSound]) -> FlowSound -> [FlowSound]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool) -> [FlowSound] -> [FlowSound]
reSyllableCntntsTup Array Int (Sound8, Bool)
tup17 ([FlowSound] -> [FlowSound])
-> (FlowSound -> [FlowSound]) -> FlowSound -> [FlowSound]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
groupSnds) ([FlowSound] -> [[FlowSound]])
-> (String -> [FlowSound]) -> String -> [[FlowSound]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowSound -> [FlowSound]
forall a. (Ord a, Num a) => [a] -> [[a]]
words1 (FlowSound -> [FlowSound])
-> (String -> FlowSound) -> String -> [FlowSound]
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 (String -> FlowSound) -> (String -> String) -> String -> FlowSound
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' then Char
' ' else Char
x)
      where words1 :: [a] -> [[a]]
words1 [a]
xs = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
ts then [] else [a]
w [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [[a]]
words1 [a]
s'' -- Practically this is an optimized version for this case 'words' function from Prelude.
              where ts :: [a]
ts = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1) [a]
xs
                    ([a]
w, [a]
s'') = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0) [a]
ts
            {-# NOINLINE words1 #-}
{-# INLINE createSyllablesUkrSTup #-}

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

-- | 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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
49 Bool -> Bool -> Bool
|| Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
66 Bool -> Bool -> Bool
|| Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
y = Bool
False
  | Sound8 -> Sound8
forall a. Num a => a -> a
abs (Sound8
x Sound8 -> Sound8 -> Sound8
forall a. Num a => a -> a -> a
- Sound8
y) Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
1 =
      Bool -> [(Sound8, Bool)] -> Sound8 -> Bool
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)]) (Sound8 -> Bool) -> (Sound8 -> Sound8) -> Sound8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sound8 -> Sound8 -> Sound8
forall a. Ord a => a -> a -> a
min Sound8
x (Sound8 -> Bool) -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
49 Bool -> Bool -> Bool
|| Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
66 Bool -> Bool -> Bool
|| Sound8
x Sound8 -> Sound8 -> Bool
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 Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
y = Bool
False
  | Sound8 -> Sound8
forall a. Num a => a -> a
abs (Sound8
x Sound8 -> Sound8 -> Sound8
forall a. Num a => a -> a -> a
- Sound8
y) Sound8 -> Sound8 -> Bool
forall a. Eq a => a -> a -> Bool
== Sound8
1 = (Bool, Array Int (Sound8, Bool)) -> Sound8 -> Bool
forall a b. Ord a => (b, Array Int (a, b)) -> a -> b
getBFst' (Bool
True, Array Int (Sound8, Bool)
tup17) (Sound8 -> Bool) -> (Sound8 -> Sound8) -> Sound8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sound8 -> Sound8 -> Sound8
forall a. Ord a => a -> a -> a
min Sound8
x (Sound8 -> Bool) -> Sound8 -> Bool
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
xSound8 -> FlowSound -> FlowSound
forall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged (Sound8
ySound8 -> FlowSound -> FlowSound
forall a. a -> [a] -> [a]
:FlowSound
xs)
  | Bool -> Bool
not (Bool -> Bool) -> (Sound8 -> Bool) -> Sound8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sound8 -> Sound8 -> Bool
notEqC Sound8
x (Sound8 -> Bool) -> Sound8 -> Bool
forall a b. (a -> b) -> a -> b
$ Sound8
y = Sound8
ySound8 -> FlowSound -> FlowSound
forall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged FlowSound
xs
  | Bool
otherwise = Sound8
xSound8 -> FlowSound -> FlowSound
forall a. a -> [a] -> [a]
:FlowSound -> FlowSound
representProlonged (Sound8
ySound8 -> FlowSound -> FlowSound
forall a. a -> [a] -> [a]
:FlowSound
xs)
representProlonged FlowSound
xs = FlowSound
xs