Copyright (C) 2009 Mathieu Boespflug This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . > module Main where This file brings together the various pieces that make up the hmk command. The core logic is in Control.Hmk. That module knows only rules, from which it can produce a schedule of recipes to run. Despite the name, it is the most generic part of the application. Rules may be generated by instantiating meta-rules, as often appears in mkfile's. Instantiation of meta-rules is done by the parser, with the help of the Metarule module. In fact most of the work is done by the parser, as it is also the parser's job to carry forward any variable substitutions. > import Control.Hmk > import Parse > import Eval > import Metarule > import Control.Monad > import Control.Applicative > import qualified Data.Sequence as Seq > import qualified Data.Foldable as Seq > import qualified Data.Map as Map > import Data.Either > import Data.Char (isAlphaNum) > import System.IO > import System.Environment > import System.Exit > import System.Console.GetOpt > > > data HmkOption = OptHelp | OptJobs Int | OptMkfile FilePath > | OptQuestion | OptAll > deriving (Eq, Ord, Show) > > options = [ Option ['a', 'B'] [] (NoArg OptAll) > "Unconditionally make all targets." > , Option ['f'] ["file"] (ReqArg OptMkfile "FILE") > "Read FILE as an mkfile." > , Option ['j'] ["jobs"] (ReqArg (OptJobs . read) "N") > "Allow N jobs at once." > , Option ['q'] ["question"] (NoArg OptQuestion) > "Run no commands; exit status says if up to date." > , Option ['h'] ["help"] (NoArg OptHelp) > "This usage information." ] > > usage = "Usage: hmk [OPTION]... [ASSIGNMENT]... [TARGET]..." > > printUsage = hPutStrLn stderr usage > > printHelp = do > let header = usage ++ "\nOptions:" > putStrLn (usageInfo header options) > > bailout = printUsage >> exitFailure The arguments given on the command line can be of the form a=b. This pins the value for variable $a to be 'b'. The following function splits out arguments of this form from the rest. > getAssignments :: [String] -> (Map.Map String (Seq.Seq String), [String]) > getAssignments args = (Map.fromList assigns, targets) where > (assigns, targets) = partitionEithers $ map p_assignment args > p_assignment arg = case span isAlphaNum arg of > (var, '=':rest) -> Left (var, Seq.fromList $ words rest) > _ -> Right arg > main :: IO () > main = do > (opts, other, errs) <- getOpt RequireOrder options <$> getArgs > unless (null errs) $ do > hPutStr stderr (concat errs) > exitFailure > when (OptHelp `elem` opts) (printHelp >> exitSuccess) > let (assigns, targets) = fmap (map File) (getAssignments other) > -- number of jobs to run simultaneously. > slots = foldr (\x y -> case x of OptJobs j -> j; _ -> y) 1 opts > mkfile = foldr (\x y -> case x of OptMkfile f -> f; _ -> y) "mkfile" opts > metarules <- eval assigns =<< parse mkfile <$> readFile mkfile > let rules = Seq.toList $ instantiateRecurse (Seq.fromList targets) metarules > let arules = if OptAll `elem` opts > then map (\r -> r{Control.Hmk.isStale = \_ _ -> return True}) rules > else rules > when (null rules) (fail "No rules in mkfile.") > -- completed and coalesced rules. > let crules = process Eval.isStale arules Question mode. > when (OptQuestion `elem` opts) $ do > let ts = if null targets then [target (head rules)] else targets > schedule <- mk crules targets > if null schedule then exitSuccess else exitFailure Per the mk man page, if no targets are specified on the command line, then assume the target is that of the first rule. > if null targets then > mkConcurrent slots crules [target (head rules)] else > mkConcurrent slots crules targets