{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Phonetic.Languages.Parsing -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- The additional parsing library functions for the lineVariantsG3 executable. -- @ since 0.3.0.0 -- module Phonetic.Languages.Parsing ( -- * Predicates isClosingCurlyBracket , isSlash , isOpeningCurlyBracket , variations -- * Transformations , breakGroupOfStrings , breakInSlashes , combineVariants , combineHeadsWithNexts , transformToVariations ) where isClosingCurlyBracket :: String -> Bool isClosingCurlyBracket = (== "}") isSlash :: String -> Bool isSlash (x:xs) | x /= '/' = False | null xs = True | otherwise = False isSlash _ = False isOpeningCurlyBracket :: String -> Bool isOpeningCurlyBracket = (== "{") breakGroupOfStrings :: [String] -> (([String],[[String]]),[String]) breakGroupOfStrings !xss = ((tss,breakInSlashes uss []), drop 1 zss) where (!yss,!zss) = break isClosingCurlyBracket xss (!tss,!uss) = (\(t1,t2) -> (t1,drop 1 t2)) . break isOpeningCurlyBracket $ yss breakInSlashes :: [String] -> [[String]] -> [[String]] breakInSlashes !wss !usss | null lss = kss : usss | otherwise = breakInSlashes (drop 1 lss) (kss : usss) where (!kss,!lss) = break isSlash wss combineVariants :: ([String],[[String]]) -> [[String]] combineVariants (!xss, (!yss:ysss)) = (xss `mappend` yss) : combineVariants (xss, ysss) combineVariants _ = [] combineHeadsWithNexts :: [[String]] -> [String] -> [[String]] combineHeadsWithNexts !xsss !yss | null yss = xsss | otherwise = combineHeadsWithNexts [xss `mappend` zss | xss <- xsss, zss <- zsss] uss where (!t,!uss) = breakGroupOfStrings yss !zsss = combineVariants t transformToVariations :: [String] -> [[String]] transformToVariations !yss | null yss = [] | otherwise = combineHeadsWithNexts xsss tss where (!y,!tss) = breakGroupOfStrings yss !xsss = combineVariants y variations :: [String] -> Bool variations xss | any isSlash xss = if any isOpeningCurlyBracket xss && any isClosingCurlyBracket xss then True else False | otherwise = False