{-| Module : Main Description : The "glue" between spreadsheets and GraphViz Copyright : (c) Oleksandr Zhabenko, 2017-2023 License : MIT Maintainer : oleksandr.zhabenko@yahoo.com Stability : Experimental A program @gvti@ converts a specially formated @.csv@ file with a colon as a field separator obtained from the electronic table into a visualized by GraphViz graph in the one of the supported by GraphViz format. The proper GraphViz installation is required. -} {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_HADDOCK -show-extensions #-} module Main where import GHC.Base import GHC.List import System.IO (readFile) import GVTI (process2) import System.Environment (getArgs) import System.Directory import Data.List (isPrefixOf, lines, unlines) import Data.Char (isLetter, isDigit) import Formatting (formatLines) main :: IO () main = do args00 <- getArgs let args = filter (/= "-g") args00 arg0 = concat . take 1 $ args arggs = drop 1 args xxs = take 1 . drop 2 . concat . filter ("-c" `isPrefixOf`) $ arggs yys = take 2 . drop 2 . concat . filter ("-f" `isPrefixOf`) $ arggs bnames = drop 2 . concat . filter ("-b" `isPrefixOf`) $ arggs splines = take 1 . drop 2 . concat . filter ("-s" `isPrefixOf`) $ arggs remAts = take 1 . drop 1 . concat . filter ("-y" `isPrefixOf`) $ arggs gvti = any (== "-g") args00 delims | any ("-d" `isPrefixOf`) arggs = drop 2 . concat . filter ("-d" `isPrefixOf`) $ arggs | otherwise = ":" exI <- doesFileExist arg0 if exI then do text2 <- readFile arg0 -- well, in the future this can be extended to also stdin. let txt | gvti = unlines . formatLines (head delims) . filter (any (\x -> isLetter x || isDigit x)) . lines $ text2 | otherwise = unlines . filter (any (\x -> isLetter x || isDigit x)) . lines $ text2 process2 delims xxs yys bnames splines remAts txt else error "Main: No file specified exists in the current directory! "