{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Data.ChooseLine
-- Copyright   :  (c) Oleksandr Zhabenko 2021-2024
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- General shared by phladiprelio-ukrainian-simple and phladiprelio-general-simple functionality to compare contents of the up to 14 files line-by-line 
-- and to choose the resulting option. 

{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-}

module Data.ChooseLine where

import GHC.Base
import Data.Foldable (mapM_) 
import Data.Maybe (fromMaybe) 
import Text.Show (Show(..))
import Text.Read (readMaybe)
import System.IO (putStrLn, FilePath,getLine,appendFile,putStr,readFile)
import Data.List
import Data.Tuple (fst,snd)
import Control.Exception (IOException,catch) 

-- | Is rewritten from the <https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Lines.html#compareFilesToOneCommon>
-- Given a list of different filepaths and the resulting filepath for the accumulated data provides a simple way to compare options of the lines in every file in the
-- first argument and to choose that option for the resulting file. Therefore, the resulting file can combine options for lines from various sources.
compareFilesToOneCommon 
 :: Int -- ^ A number of files to be read and treated as sources of lines to choose from.
 -> [FilePath] 
 -> FilePath 
 -> IO ()
compareFilesToOneCommon :: Int -> [FilePath] -> FilePath -> IO ()
compareFilesToOneCommon Int
n [FilePath]
files FilePath
file3 = do
 [(Int, [(Int, FilePath)])]
contentss <- ((Int, FilePath) -> IO (Int, [(Int, FilePath)]))
-> [(Int, FilePath)] -> IO [(Int, [(Int, FilePath)])]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((\(Int
j,FilePath
ks) -> do {FilePath -> IO FilePath
readFileIfAny FilePath
ks IO FilePath
-> (FilePath -> IO (Int, [(Int, FilePath)]))
-> IO (Int, [(Int, FilePath)])
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilePath
fs -> (Int, [(Int, FilePath)]) -> IO (Int, [(Int, FilePath)])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
j, [Int] -> [FilePath] -> [(Int, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] ([FilePath] -> [(Int, FilePath)])
-> (FilePath -> [FilePath]) -> FilePath -> [(Int, FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
lines (FilePath -> [(Int, FilePath)]) -> FilePath -> [(Int, FilePath)]
forall a b. (a -> b) -> a -> b
$ FilePath
fs)})) ([(Int, FilePath)] -> IO [(Int, [(Int, FilePath)])])
-> ([FilePath] -> [(Int, FilePath)])
-> [FilePath]
-> IO [(Int, [(Int, FilePath)])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [FilePath] -> [(Int, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] ([FilePath] -> [(Int, FilePath)])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [(Int, FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [FilePath] -> [FilePath]
forall a. Int -> [a] -> [a]
take Int
n ([FilePath] -> IO [(Int, [(Int, FilePath)])])
-> [FilePath] -> IO [(Int, [(Int, FilePath)])]
forall a b. (a -> b) -> a -> b
$ [FilePath]
files
 [(Int, [(Int, FilePath)])] -> FilePath -> IO ()
compareF [(Int, [(Int, FilePath)])]
contentss FilePath
file3
   where compareF :: [(Int,[(Int,String)])] -> FilePath -> IO ()
         compareF :: [(Int, [(Int, FilePath)])] -> FilePath -> IO ()
compareF [(Int, [(Int, FilePath)])]
ysss FilePath
file3 = (Int -> IO ()) -> [Int] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Int
i -> do
          FilePath -> IO ()
putStr FilePath
"Please, specify which variant to use as the result, "
          FilePath -> IO ()
putStrLn FilePath
"maximum number is the quantity of the files from which the data is read: "
          let strs :: [(Int, FilePath)]
strs = ((Int, [(Int, FilePath)]) -> (Int, FilePath))
-> [(Int, [(Int, FilePath)])] -> [(Int, FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
j,[(Int, FilePath)]
ks) -> (\[(Int, FilePath)]
ts -> if [(Int, FilePath)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, FilePath)]
ts then (Int
j,FilePath
"")
                      else let (Int
_,FilePath
rs) = [(Int, FilePath)] -> (Int, FilePath)
forall a. HasCallStack => [a] -> a
head [(Int, FilePath)]
ts in  (Int
j,FilePath
rs)) ([(Int, FilePath)] -> (Int, FilePath))
-> ([(Int, FilePath)] -> [(Int, FilePath)])
-> [(Int, FilePath)]
-> (Int, FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                       ((Int, FilePath) -> Bool) -> [(Int, FilePath)] -> [(Int, FilePath)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i) (Int -> Bool)
-> ((Int, FilePath) -> Int) -> (Int, FilePath) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, FilePath) -> Int
forall a b. (a, b) -> a
fst) ([(Int, FilePath)] -> (Int, FilePath))
-> [(Int, FilePath)] -> (Int, FilePath)
forall a b. (a -> b) -> a -> b
$ [(Int, FilePath)]
ks) [(Int, [(Int, FilePath)])]
ysss
          FilePath -> IO ()
putStrLn (FilePath -> IO ())
-> ([(Int, FilePath)] -> FilePath) -> [(Int, FilePath)] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines ([FilePath] -> FilePath)
-> ([(Int, FilePath)] -> [FilePath])
-> [(Int, FilePath)]
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, FilePath) -> FilePath) -> [(Int, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
i,FilePath
xs) -> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
i FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
":\t" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
xs) ([(Int, FilePath)] -> IO ()) -> [(Int, FilePath)] -> IO ()
forall a b. (a -> b) -> a -> b
$ [(Int, FilePath)]
strs
          FilePath
ch <- IO FilePath
getLine
          let choice2 :: Int
choice2 = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (FilePath -> Maybe Int
forall a. Read a => FilePath -> Maybe a
readMaybe FilePath
ch::Maybe Int)
          FilePath -> [FilePath] -> IO ()
toFileStr FilePath
file3 ((\[(Int, FilePath)]
us -> if [(Int, FilePath)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, FilePath)]
us then [FilePath
""] else [(Int, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ((Int, FilePath) -> FilePath)
-> ([(Int, FilePath)] -> (Int, FilePath))
-> [(Int, FilePath)]
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, FilePath)] -> (Int, FilePath)
forall a. HasCallStack => [a] -> a
head ([(Int, FilePath)] -> FilePath) -> [(Int, FilePath)] -> FilePath
forall a b. (a -> b) -> a -> b
$ [(Int, FilePath)]
us]) ([(Int, FilePath)] -> [FilePath])
-> ([(Int, FilePath)] -> [(Int, FilePath)])
-> [(Int, FilePath)]
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, FilePath) -> Bool) -> [(Int, FilePath)] -> [(Int, FilePath)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
choice2) (Int -> Bool)
-> ((Int, FilePath) -> Int) -> (Int, FilePath) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, FilePath) -> Int
forall a b. (a, b) -> a
fst) ([(Int, FilePath)] -> [FilePath])
-> [(Int, FilePath)] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ [(Int, FilePath)]
strs)) ([Int] -> IO ()) -> [Int] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Int
1..]

{-| Inspired by: 'https://hackage.haskell.org/package/base-4.15.0.0/docs/src/GHC-IO.html#catch' 
 Is taken from the 
https://hackage.haskell.org/package/string-interpreter-0.8.0.0/docs/src/Interpreter.StringConversion.html#readFileIfAny
to reduce general quantity of dependencies.
Reads a textual file given by its 'FilePath' and returns its contents lazily. If there is
some 'IOException' thrown or an empty file then returns just "". Raises an exception for the binary file. -}
readFileIfAny :: FilePath -> IO String
readFileIfAny :: FilePath -> IO FilePath
readFileIfAny FilePath
file = IO FilePath -> (IOException -> IO FilePath) -> IO FilePath
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (FilePath -> IO FilePath
readFile FilePath
file) (\(IOException
_ :: IOException) -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"")
{-# INLINE readFileIfAny #-}

-- | Prints list of 'String's to the file as a multiline 'String' with default line ending. Uses 'appendFile' function inside.
toFileStr ::
  FilePath -- ^ The 'FilePath' to the file to be written in the 'AppendMode' (actually appended with) the information output.
  -> [String] -- ^ Each element is appended on the new line to the file.
  -> IO ()
toFileStr :: FilePath -> [FilePath] -> IO ()
toFileStr FilePath
file = FilePath -> FilePath -> IO ()
appendFile FilePath
file (FilePath -> IO ())
-> ([FilePath] -> FilePath) -> [FilePath] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines
{-# INLINE toFileStr #-}