-- | -- Module : Phonetic.Languages.General.GetInfo.Parsing -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Can be used to analyze a poetic text in a phonetic language, for every line printing statistic data. -- {-# OPTIONS_GHC -threaded #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns, FlexibleContexts #-} module Phonetic.Languages.General.GetInfo.Parsing where import Phonetic.Languages.General.GetTextualInfo import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import System.Environment (getArgs) import Data.Monoid (mappend) import Phonetic.Languages.General.Common import Phonetic.Languages.General.Lines import Data.Phonetic.Languages.PrepareText import Phonetic.Languages.General.Lines import Data.List (sort) import GHC.Arr import Data.Phonetic.Languages.Base import Data.Phonetic.Languages.Syllables import Data.Phonetic.Languages.SpecificationsRead import Phonetic.Languages.General.Simple.Parsing import Phonetic.Languages.Array.General.PropertiesSyllablesG2 import Phonetic.Languages.General.Simple import Data.Phonetic.Languages.SpecificationsRead -- | The first 4 arguments are the file names with the specifications. -- 1) with the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema); -- -- 2) with the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's; -- -- 3) with the 'SegmentRulesG' specifications only; -- -- 4) with the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). -- argsToGetInfoProcessment :: (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function. -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> IO () argsToGetInfoProcessment h qs = do args40 <- getArgs let (!args14,!args000) = splitAt 4 args40 [fileGWrSys, controlFile, segmentRulesFile, concatenationsFileP] = args14 files4ArgsProcessment fileGWrSys controlFile segmentRulesFile concatenationsFileP h qs args000 files4ArgsProcessment :: FilePath -- ^ With the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema); -> FilePath -- ^ With the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's; -> FilePath -- ^ With the 'SegmentRulesG' specifications only; -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function. -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> [String] -- ^ List of other command line arguments -> IO () files4ArgsProcessment !fileGWrSys !controlFile !segmentRulesFile !concatenationsFileP h qs args000 = do let !args00 = filter (\ts -> take 2 ts /= "+X" && ts /= "++B") args000 !lstW = any (== "++B") args000 !args0 = takeWhile (/= "+M") args00 `mappend` drop 1 (dropWhile (/= "-M") args00) !multiples = drop 1 . dropWhile (/= "+M") . takeWhile (/= "-M") $ args00 -- Arguments for multiple metrices mode !args = filter (\xs -> all (/= ':') xs && all (/= '@') xs) args0 !coeffs = readCF . concat . take 1 $ args !coeffsWX = readCF . drop 2 . concat . take 1 . filter (\ts -> take 2 ts == "+X") $ args000 !lInes = filter (any (== ':')) args0 !numbersJustPrint = filter (== "@n") args0 (!wrs, !ks, !arr, !gs, !js, !vs, !ysss, !xs) = innerProcessmentSimple fileGWrSys controlFile segmentRulesFile concatenationsFileP if isPair coeffs then do let !file = concat . drop 1 . take 2 $ args if null numbersJustPrint then do let !gzS = concat . take 1 . drop 2 $ args !printLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 3 $ args)::(Maybe Int)) !toOneLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 4 $ args)::(Maybe Int)) !choice = concat . drop 5 . take 6 $ args generalProc wrs ks arr gs h qs ysss xs js vs {- the old arguments follow -} lstW multiples lInes coeffs coeffsWX file gzS printLine toOneLine choice else do contents <- readFile file fLinesIO ysss xs js vs contents else do let !file = concat . take 1 $ args if null numbersJustPrint then do let !gzS = concat . take 1 . drop 1 $ args !printLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 2 $ args)::(Maybe Int)) !toOneLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 3 $ args)::(Maybe Int)) !choice = concat . drop 4 . take 5 $ args generalProc wrs ks arr gs h qs ysss xs js vs {- the old arguments follow -} lstW multiples lInes coeffs coeffsWX file gzS printLine toOneLine choice else do contents <- readFile file fLinesIO ysss xs js vs contents