Skip to content
Snippets Groups Projects
Commit da79719d authored by Alice Brenon's avatar Alice Brenon
Browse files

Add a command-line interface to allow processing stdin or a given file and...

Add a command-line interface to allow processing stdin or a given file and create files corresponding to both parts of the XML (raw text / empty tree structure)
parent 50dc0c6e
No related branches found
No related tags found
No related merge requests found
......@@ -36,9 +36,13 @@ library
executable invisiXML
main-is: Main.hs
other-modules: CLI
, Paths_InvisiXML
build-depends: base >=4.12 && <4.15
, filepath
, InvisiXML
, mtl
, optparse-applicative
, text
hs-source-dirs: app
default-language: Haskell2010
......
module CLI (
Command(..)
, Input(..)
, getCommand
) where
import Data.Version (showVersion)
import Control.Applicative ((<*>), optional)
import Options.Applicative (
Parser, ReadM, argument, execParser, fullDesc, header
, help, helper, info, long, metavar, option, short, str, switch, value
)
import qualified Paths_InvisiXML as InvisiXML (version)
data Input = StdIn | FileInput FilePath
data Command = Command {
input :: Input
, outputPrefix :: Maybe FilePath
, pristine :: Bool
}
inputArg :: ReadM Input
inputArg = fileOrStdIn <$> str
where
fileOrStdIn "-" = StdIn
fileOrStdIn f = FileInput f
command :: Parser Command
command = Command
<$> argument inputArg (metavar "INPUT_FILE" <> value StdIn
<> help "XML file to process"
)
<*> option (optional str) (short 'o' <> long "outputPrefix" <> value Nothing
<> help "prefix for the output files"
)
<*> switch (short 'p' <> long "pristine"
<> help "keep input exactly as is, not unindenting or normalizing it in any way"
)
getCommand :: IO Command
getCommand = execParser $
info
(helper <*> command)
(fullDesc <> header ("InvisiXML v" ++ showVersion InvisiXML.version))
{-# LANGUAGE NamedFieldPuns #-}
module Main where
import CLI (Command(..), Input(..), getCommand)
import Control.Monad.Except (runExceptT)
import qualified Data.Text.IO as Text (putStr)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text.IO as Text (getContents, readFile, writeFile)
import Text.InvisiXML (InvisiXML(..), parse)
import Text.XML.Light.Serializer (encode)
import System.FilePath ((<.>), dropExtension)
main :: IO ()
main = getContents >>= runExceptT . parse >>= either (fail . show) display
endPoints :: Command -> (IO Text, FilePath)
endPoints (Command {input = StdIn, outputPrefix}) =
(Text.getContents, fromMaybe noOutputPrefix outputPrefix)
where
noOutputPrefix = error "output prefix (-o) is necessary when running on stdin"
endPoints (Command {input = FileInput f, outputPrefix}) =
(Text.readFile f, fromMaybe (dropExtension f) outputPrefix)
run :: Command -> IO ()
run command =
source >>= runExceptT . parse >>= either (fail . show) create
where
display result = do
Text.putStr $ text result
putStr . encode $ structure result
(source, prefix) = endPoints command
create (InvisiXML {text, structure}) = do
Text.writeFile (prefix <.> "txt") text
writeFile (prefix <.> "ixml") $ encode structure
main :: IO ()
main = getCommand >>= run
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment