master-plan/app/Main.hs

120 lines
5.8 KiB
Haskell
Raw Normal View History

2017-08-10 04:32:46 +03:00
{-|
Module : Main
Description : Parses command line and dispatches to correct backend
Copyright : (c) Rodrigo Setti, 2017
License : MIT
Maintainer : rodrigosetti@gmail.com
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE UnicodeSyntax #-}
2017-08-10 04:17:13 +03:00
module Main (main) where
2017-08-05 04:53:52 +03:00
2017-08-10 04:17:13 +03:00
import Data.List (intercalate)
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as M
2017-08-10 04:32:46 +03:00
import Data.Maybe (catMaybes, fromMaybe)
2017-08-09 22:48:09 +03:00
import Data.Semigroup ((<>))
2017-08-10 05:20:47 +03:00
import qualified Data.Text.IO as TIO
2017-08-12 21:10:44 +03:00
import MasterPlan.Backend.Graph
2017-08-09 22:48:09 +03:00
import MasterPlan.Data
import qualified MasterPlan.Parser as P
import Options.Applicative
2017-08-12 21:10:44 +03:00
import System.IO (hPutStr, stderr, stdin)
2017-08-09 22:48:09 +03:00
-- |Type output from the command line parser
2017-08-12 21:10:44 +03:00
data Opts = Opts { inputPath :: Maybe FilePath
, outputPath :: Maybe FilePath
, projFilter :: ProjFilter -- ^ filter to consider
, renderOptions :: RenderOptions }
2017-08-09 22:48:09 +03:00
deriving (Show)
2017-08-12 21:10:44 +03:00
newtype ProjFilter = ProjFilter (ProjectSystem -> Project Bool)
2017-08-09 22:48:09 +03:00
2017-08-10 04:17:13 +03:00
noFilter ProjFilter
2017-08-12 21:10:44 +03:00
noFilter = ProjFilter $ const $ const True
2017-08-10 04:17:13 +03:00
2017-08-09 22:48:09 +03:00
instance Show ProjFilter where
show _ = "ProjFilter"
readEnum [(String, a)] ReadM a
readEnum mapping = maybeReader $ flip lookup mapping
-- |The command line parser
cmdParser Parser Opts
2017-08-12 21:10:44 +03:00
cmdParser = Opts <$> optional (strArgument ( help "plan file to read from (default from stdin)"
<> metavar "FILENAME" ))
2017-08-09 22:48:09 +03:00
<*> optional (strOption ( long "output"
<> short 'o'
2017-08-12 21:10:44 +03:00
<> help "output file name (.png, .tif, .bmp, .jpg and .pdf supported)"
2017-08-09 22:48:09 +03:00
<> metavar "FILENAME" ))
2017-08-10 04:17:13 +03:00
<*> (filterParser <|> pure noFilter)
2017-08-12 21:10:44 +03:00
<*> renderOptionsParser
2017-08-09 22:48:09 +03:00
where
2017-08-12 21:10:44 +03:00
renderOptionsParser :: Parser RenderOptions
renderOptionsParser = RenderOptions <$> switch ( long "color"
<> short 'c'
<> help "color each project by progress")
<*> option auto ( long "width"
<> short 'w'
<> help "width of the output image"
<> value (-1)
<> metavar "NUMBER")
<*> option auto ( long "height"
<> help "height of the output image"
<> value (-1)
<> metavar "NUMBER")
<*> strOption ( long "root"
<> short 'r'
<> help "name of the root project definition"
<> value "root"
<> showDefault
<> metavar "NAME")
<*> (invertProps <$> many (option property ( long "hide"
<> help "hide a particular property"
<> metavar (intercalate "|" $ map fst propertyNames))))
2017-08-10 04:17:13 +03:00
propertyNames = map (\p -> (show p, p)) [minBound :: ProjProperty ..]
property = readEnum propertyNames
2017-08-09 22:48:09 +03:00
invertProps [ProjProperty] [ProjProperty]
2017-08-10 04:17:13 +03:00
invertProps l = filter (`notElem` l) $ map snd propertyNames
2017-08-09 22:48:09 +03:00
filterParser Parser ProjFilter
filterParser = (ProjFilter . mkProgressFilter) <$> option auto ( long "progress-below"
<> help "only display projects which progress is < N%"
<> metavar "N" )
where
2017-08-12 21:10:44 +03:00
mkProgressFilter n sys p = progress sys p * 100 < n
main IO ()
2017-08-09 22:48:09 +03:00
main = masterPlan =<< execParser opts
where
opts = info (cmdParser <**> helper)
( fullDesc
<> progDesc "See documentation on how to write project plan files"
<> header "master-plan - project management tool for hackers" )
2017-08-10 04:17:13 +03:00
filterBinding ProjectSystem ProjFilter ProjectBinding Maybe ProjectBinding
2017-08-12 21:10:44 +03:00
filterBinding sys (ProjFilter f) (ExpressionProj r e) = ExpressionProj r <$> filterProj e
2017-08-10 04:17:13 +03:00
where
2017-08-12 21:10:44 +03:00
filterProj p@(SumProj ps) = filterHelper p ps SumProj
filterProj p@(ProductProj ps) = filterHelper p ps ProductProj
filterProj p@(SequenceProj ps) = filterHelper p ps SequenceProj
filterProj p = if f sys p then Just p else Nothing
2017-08-10 04:17:13 +03:00
2017-08-12 21:10:44 +03:00
filterHelper p ps c = if f sys p then c <$> filterProjs ps else Nothing
2017-08-10 04:17:13 +03:00
filterProjs ps = NE.nonEmpty (catMaybes $ NE.toList $ NE.map filterProj ps)
2017-08-12 21:10:44 +03:00
2017-08-10 04:17:13 +03:00
filterBinding _ _ b = Just b
2017-08-09 22:48:09 +03:00
masterPlan Opts IO ()
2017-08-10 04:17:13 +03:00
masterPlan opts =
2017-08-12 21:10:44 +03:00
do contents <- maybe (TIO.hGetContents stdin) TIO.readFile $ inputPath opts
case P.runParser (fromMaybe "stdin" $ inputPath opts) contents of
2017-08-10 04:17:13 +03:00
Left e -> hPutStr stderr e
Right sys@(ProjectSystem b) ->
2017-08-12 21:10:44 +03:00
do let sys' = optimizeSys $ ProjectSystem $ M.mapMaybe
2017-08-10 04:17:13 +03:00
(filterBinding sys $ projFilter opts) b
2017-08-12 21:10:44 +03:00
let outfile = fromMaybe (fromMaybe "output" (outputPath opts) ++ ".pdf") $ outputPath opts
render outfile (renderOptions opts) sys'