module Guguk.Morphology.Phonology
(vowelHarmony, aTypeHarmony, iTypeHarmony,
firstConsonantAlteration, lastConsonantAlteration) where
import Data.Maybe
import qualified Data.List as L
import qualified Data.Text as T
import qualified Guguk.TurkishAlphabet as Alph
import qualified Guguk.Phonetics as Ph
import qualified Guguk.Syllabification as Syl
same :: (Eq a) => [a] -> Bool
same xs = and $ zipWith (==) xs (tail xs)
lastSyllable :: T.Text -> String
lastSyllable w = T.unpack $ last (Syl.syllabify w)
lastVowel :: T.Text -> Char
lastVowel w = fromMaybe (error "Syllable without a vowel.")
(L.find Alph.isVowel $ lastSyllable w)
vowelHarmony :: T.Text -> Bool
vowelHarmony t = same $ map Ph.vowelLocation vowelPhoneme
where vowelList = T.unpack $ T.filter Alph.isVowel t
vowelPhoneme = map (head . Alph.getPhonemes) vowelList
aTypeHarmony :: T.Text -> Char
aTypeHarmony w = case loc of
Ph.Back -> 'a'
Ph.Front -> 'e'
_ -> error "Unknown vowel location."
where loc = Ph.vowelLocation $ head $ Ph.getBySurfaceForm $ T.singleton (lastVowel w)
iTypeHarmony :: T.Text -> Char
iTypeHarmony w = case (Ph.vowelLocation lV, Ph.vowelRoundedness lV) of
(Ph.Back, Ph.Unrounded) -> 'ı'
(Ph.Back, Ph.Rounded) -> 'u'
(Ph.Front, Ph.Unrounded) -> 'i'
(Ph.Front, Ph.Rounded) -> 'ü'
_ -> error "Unknown vowel location and roundedness."
where lV = head $ Ph.getBySurfaceForm $ T.singleton $ lastVowel w
harden :: Char -> Char
harden 'c' = 'ç'
harden 'd' = 't'
harden x = x
soften :: Char -> Char
soften 'p' = 'b'
soften 'ç' = 'c'
soften 'k' = 'ğ'
soften 't' = 'd'
soften 'g' = 'ğ'
soften x = x
firstConsonantAlteration :: T.Text -> T.Text -> (T.Text, T.Text)
firstConsonantAlteration w1 w2
| isVoiceless (T.last w1) = (w1, T.cons (harden $ T.head w2) (T.tail w2))
| otherwise = (w1, w2)
where isVoiceless c = Ph.Voiceless == Ph.consonantVoice firstPhoneme
where firstPhoneme = head $ Ph.getBySurfaceForm $ T.singleton c
lastConsonantAlteration :: T.Text -> T.Text -> (T.Text, T.Text)
lastConsonantAlteration w1 w2
| Alph.isVowel (T.head w2) = (T.snoc (T.init w1) (soften $ T.last w1), w2)
| otherwise = (w1, w2)