-- | -- Module : Data.Phonetic.Languages.SpecificationsRead -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- {-| Provides functions to read data specifications for other modules from textual files. -} module Data.Phonetic.Languages.SpecificationsRead where import Data.Char (isAlpha) import Numeric.Wrapper.R.GLPK.Phonetic.Languages.Durations import System.Environment (getArgs) import GHC.Arr import Text.Read import Data.List import Data.Maybe (fromMaybe,fromJust) import GHC.Int import Data.Phonetic.Languages.Base charLine :: Char -> String -> Bool charLine c = (== [c]) . take 1 groupBetweenChars :: Char -> [String] -> [[String]] groupBetweenChars c [] = [] groupBetweenChars c xs = css : groupBetweenChars c (dropWhile (charLine c) dss) where (css,dss) = span (charLine c) xs getGWritingSystem :: Char -> String -> GWritingSystemPRPLX getGWritingSystem c xs = map ((\(t1,t2) -> (sort . map (\kt -> fromJust (readPEMaybe kt::Maybe PhoneticsRepresentationPLX)) $ t2, read (concat t1)::Int8)) . splitAt 1) . groupBetweenChars c . lines $ xs