module Guguk.Syllabification
(syllabify, Syllable) where
import Data.Char (isAlpha, toLower)
import Data.Maybe (fromJust, isJust, isNothing)
import qualified Data.Text as T
import qualified Guguk.TurkishAlphabet as Alph
type Syllable = T.Text
charAt :: T.Text -> Int -> Maybe Char
charAt xs i = if T.length xs > i then Just (xs `T.index` i) else Nothing
substring :: Int -> Int -> T.Text -> T.Text
substring x y = T.drop x . T.take y
elemT :: Char -> T.Text -> Bool
elemT c t = isJust $ T.find (==c) t
syllabify :: T.Text -> [Syllable]
syllabify s
| T.null s = []
| '\'' `elemT` T.tail s = concatMap syllabify (T.splitOn "'" s)
| isNothing firstVowelIndex = [xs]
| isNothing (afterVowel 1) = [xs]
| Alph.isVowel(fromJust $ afterVowel 1) = handleSubstring 1
| isNothing (afterVowel 2) = [xs]
| Alph.isVowel(fromJust $ afterVowel 2) = handleSubstring 1
| isNothing (afterVowel 3) = [xs]
| Alph.isVowel(fromJust $ afterVowel 3) = handleSubstring 2
| lastPart `elem` exceptions = handleSubstring 2
| otherwise = handleSubstring 3
where xs = (T.filter isAlpha . T.map toLower) s
firstVowelIndex = T.findIndex Alph.isVowel xs
fVI = fromJust firstVowelIndex
len = T.length xs
lastPart = substring 2 5 xs
exceptions = ["str", "ktr", "mtr", "nsp"]
afterVowel i = fromJust $ fmap (charAt xs . (+i)) firstVowelIndex
handleSubstring n =
substring 0 (fVI + n) xs : syllabify(substring (fVI + n) len xs)