-- |
-- 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 :: Char -> [Char] -> Bool
charLine Char
c = (forall a. Eq a => a -> a -> Bool
== [Char
c]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take Int
1

groupBetweenChars
 :: Char  -- ^ A delimiter (can be used probably multiple times) used between different parts of the data.
 -> [String] -- ^ A list of 'String' that is partitioned using the 'String' starting with the delimiter.
 -> [[String]]
groupBetweenChars :: Char -> [[Char]] -> [[[Char]]]
groupBetweenChars Char
c [] = []
groupBetweenChars Char
c [[Char]]
xs = [[Char]]
css forall a. a -> [a] -> [a]
: Char -> [[Char]] -> [[[Char]]]
groupBetweenChars Char
c (forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> [Char] -> Bool
charLine Char
c) [[Char]]
dss)
  where ([[Char]]
css,[[Char]]
dss) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> [Char] -> Bool
charLine Char
c) [[Char]]
xs

{-| An example of the needed data structure to be read correctly is in the file gwrsysExample.txt in the source tarball. 
-}
getGWritingSystem
  :: Char -- ^ A delimiter (cab be used probably multiple times) between different parts of the data file. Usually, a tilda sign \'~\'.
  -> String -- ^ Actually the 'String' that is read into the result. 
  -> GWritingSystemPRPLX -- ^ The data is used to obtain the phonetic language representation of the text.
getGWritingSystem :: Char -> [Char] -> GWritingSystemPRPLX
getGWritingSystem Char
c [Char]
xs = forall a b. (a -> b) -> [a] -> [b]
map ((\([[Char]]
t1,[[Char]]
t2) -> (forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\[Char]
kt -> forall a. HasCallStack => Maybe a -> a
fromJust (forall a. PhoneticElement a => [Char] -> Maybe a
readPEMaybe [Char]
kt::Maybe PhoneticsRepresentationPLX)) forall a b. (a -> b) -> a -> b
$ [[Char]]
t2,
         forall a. Read a => [Char] -> a
read (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Char]]
t1)::Int8)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> ([a], [a])
splitAt Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> [[Char]] -> [[[Char]]]
groupBetweenChars Char
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [[Char]]
lines forall a b. (a -> b) -> a -> b
$ [Char]
xs