-- | -- Module : System.Process.Sequential -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- This library is intended to be a testsuite for some recursive multi file multiprocessment using some system executable -- that processes multiple files creating the resulting one (the \"sox\" can be a good example). -- -- The purposes are to avoid leakage of resources if the -- number of files are too great to be processed at once, to use multiple sequential processment schemes for the same -- executable and to create to some extent complex processment environment. Nevertheless, there is no guarantees that -- the test will be successful and such an environment can be created using such a scheme. Please, do not use at the moment -- in the production without additional thorough testing. module System.Process.Sequential where import Data.List (isPrefixOf) import Data.Maybe (mapMaybe, fromJust) import Data.Monoid (mappend) import System.Process (readProcessWithExitCode) import System.Directory (listDirectory,doesFileExist,removeFile) import System.Exit (ExitCode(..)) import EndOfExe (showE) import Sublists (intoRegularSublists) seqFlsReadProcessWithExitCode :: FilePath -- ^ A name of the executable that must be available inside the variable PATH. -> Int -- ^ A limiting parameter for the number of cycles. -> (String -> String) -- ^ A function to convert the name of the files in the current directory that are sequentially processed. -> String -- ^ A needed symbol sequence to be found firstly to filter the needed files to be processed by the first recursion pass. -> [Int] -- ^ A list of the length of the needed file sequences for the 'intoRegularSublists' function. -> ([Int] -> [Int]) -- ^ A function to change the previous parameter at the each step of recursive call. -> ([String] -> Int -> [String]) -- ^ A function to change the list of arguments applied after the file names as command line arguments for the executable. An 'Int' is used to additionally control the processment. -> [String] -- ^ A list of the first pass command line arguments for the executable after the file names. -> String -- ^ A parameter for the 'readProcessWithExitCode' -- the last one. Is often []. -> IO ([FilePath],[Int],[String],Int) -- ^ The result to be obtained if the processment is successful. seqFlsReadProcessWithExitCode executable limK f searchNeedle1 ns g_N h_S xss ys = do ends1 <- seqFlsReadProcessWithExitCode1 executable f searchNeedle1 ns xss ys recursiveApplyFGH executable (limK - 1) f ends1 (g_N ns) g_N h_S (h_S xss (limK - 1)) ys seqFlsReadProcessWithExitCode1 :: FilePath -- ^ A name of the executable that must be available inside the variable PATH. -> (String -> String) -- ^ A function to convert the name of the files in the current directory that are sequentially processed. -> String -- ^ A needed symbol sequence to be found firstly to filter the needed files to be processed by the first recursion pass. -> [Int] -- ^ A list of the length of the needed file sequences for the 'intoRegularSublists' function. -> [String] -- ^ A list of the first pass command line arguments for the executable after the file names. -> String -- ^ A parameter for the 'readProcessWithExitCode' -- the last one. Is often []. -> IO [FilePath] -- ^ The result to be obtained if the processment is successful. seqFlsReadProcessWithExitCode1 executable f searchNeedle ns xss ys = do dir <- listDirectory "." let zss = filter (isPrefixOf searchNeedle) dir yss = filter (not . null) . intoRegularSublists ns $ zss ends1 = map (f . last) yss y1ss = zipWith (\xss rs -> xss ++ [rs]) yss ends1 mapM_ (\uss -> seqFlsHelp1 executable uss xss ys) y1ss return ends1 seqFlsReadProcessWithExitCode0 :: FilePath -- ^ A name of the executable that must be available inside the variable PATH. -> (String -> String) -- ^ A function to convert the name of the files in the current directory that are sequentially processed. -> [Int] -- ^ A list of the length of the needed file sequences for the 'intoRegularSublists' function. -> [FilePath] -- ^ A list of the files that are processed (the existing ones plus the new one in that order). -> [String] -- ^ A list of the first pass command line arguments for the executable after the file names. -> String -- ^ A parameter for the 'readProcessWithExitCode' -- the last one. Is often []. -> IO ([FilePath],[Int],[String]) -- ^ The result to be obtained if the processment is successful. seqFlsReadProcessWithExitCode0 executable f ns zss xss ys = do let yss = filter (not . null) . intoRegularSublists ns $ zss ends1 = map (f . last) yss y1ss = zipWith (\xss rs -> xss ++ [rs]) yss ends1 mapM_ (\uss -> seqFlsHelp1 executable uss xss ys) y1ss return (ends1, ns, xss) recursiveApplyFGH :: FilePath -- ^ A name of the executable that must be available inside the variable PATH. -> Int -- ^ A limiting parameter for the number of cycles. -> (String -> String) -- ^ A function to convert the name of the files in the current directory that are sequentially processed. -> [FilePath] -- ^ A list of the files that are processed (the existing ones plus the new one in that order). -> [Int] -- ^ A list of the length of the needed file sequences for the 'intoRegularSublists' function. -> ([Int] -> [Int]) -- ^ A function to change the previous parameter at the each step of recursive call. -> ([String] -> Int -> [String]) -- ^ A function to change the list of arguments applied after the file names as command line arguments for the executable. An 'Int' is used to additionally control the processment. -> [String] -- ^ A list of the first pass command line arguments for the executable after the file names. -> String -- ^ A parameter for the 'readProcessWithExitCode' -- the last one. Is often []. -> IO ([FilePath],[Int],[String],Int) -- ^ The result to be obtained if the processment is successful. recursiveApplyFGH executable limK f zss ns g_N h_S xss ys | limK > 0 = do (ends1, ns, xss) <- seqFlsReadProcessWithExitCode0 executable f ns zss xss ys let newNs = g_N ns newXss = h_S xss (limK - 1) recursiveApplyFGH executable (limK - 1) f ends1 newNs g_N h_S newXss ys | otherwise = return (zss, ns, xss, limK) seqFlsHelp1 :: FilePath -- ^ A name of the executable that must be available inside the variable PATH. -> [FilePath] -- ^ A list of the files that are processed (the existing ones plus the new one in that order). -> [String] -- ^ A list of the first pass command line arguments for the executable after the file names. -> String -- ^ A parameter for the 'readProcessWithExitCode' -- the last one. Is often []. -> IO ExitCode -- ^ The result to be obtained. 'ExitSuccess' means that the processment was successful. seqFlsHelp1 executable files args poststr = do (code,hout,herr) <- readProcessWithExitCode (fromJust (showE executable)) (files `mappend` args) poststr case code of ExitSuccess -> putStr hout _ -> do exi <- doesFileExist (last files) if exi then removeFile (last files) >> putStrLn "System.Process.Sequential.seqFlsHelp1: not successful operation. " >> putStrLn herr else putStrLn "System.Process.Sequential.seqFlsHelp1: not successful operation. " >> putStrLn herr return code