module Development.Hake (
Rule
, hake
, hakeT
, hakefileIs
, base
, dflt
, deps
, mkfl
, addDeps
, delRules
, setCmd
, systemE
, rawSystemE
, isSuffixOf
, changeSuffix
, getVals
, getNewers
, ExitCode(ExitSuccess, ExitFailure)
, const2
) where
import System.Environment (getArgs)
import System.Exit (ExitCode(ExitSuccess, ExitFailure))
import System.Directory (doesFileExist)
import Development.Hake.DirectoryTools (maybeGetModificationTime)
import System.IO.Unsafe (unsafeInterleaveIO)
import Control.Monad.Trans (lift)
import Control.Monad.Reader (ReaderT(runReaderT), asks)
import Control.Monad.Tools (whenM)
import Control.Applicative ((<$>))
import Data.List (isSuffixOf, isPrefixOf)
import Data.List.Tools (dropUntil, isIncludedElem)
import Data.Maybe (listToMaybe, catMaybes)
import Data.Bool.Tools ((&&&), (|||))
import Data.Function.Tools (const2)
import Development.Hake.Core (traceRule, applyRule)
import Development.Hake.RunHake (runHake)
import Development.Hake.Tools (orDie, changeSuffix, systemE, rawSystemE)
import Development.Hake.Types (Rule, RuleInner, ruleToRuleInner,
Targets, Sources, Commands,
MadeFromList, ruleRetToMadeFromList,
getUpdateStatus)
import Development.Hake.Variables (hakefileUpdateOption, defaultTrgtStr)
hake :: [ Rule ] -> IO ()
hake rl = do args <- filter (notElem '=') <$> getArgs
let ud = elem hakefileUpdateOption args
trgts = filter (/=hakefileUpdateOption) args
mapM_ (hakeTarget ud (map ruleToRuleInner rl)) trgts
hakeT :: [ Rule ] -> FilePath -> IO ()
hakeT = hakeTarget True . map ruleToRuleInner
hakefileIs :: FilePath -> [ FilePath ] -> IO ExitCode
hakefileIs src others = getArgs >>= runHake src src others
hakeTarget :: Bool -> [ RuleInner ] -> FilePath -> IO ()
hakeTarget ud rls fn = do
rrls <- traceRule unsafeInterleaveIO doesFileExist fn rls
case rrls of
[] -> error $ "No usable rules for make target '" ++ fn ++ "'"
r:_ -> flip runReaderT (ud, ruleRetToMadeFromList r) $ mapM_ applyRule
$ reverse r
addDeps :: [ Rule ] -> [ (FilePath, [FilePath]) ] -> [ Rule ]
addDeps rls adrls = concatMap ad adrls ++ map dels rls
where
ad :: (FilePath, [FilePath]) -> [ Rule ]
ad (t, ss) = [ ((==t), const $ sgen t ++ ss, c) |
(testT, sgen, c) <- rls, testT t ]
dels :: Rule -> Rule
dels r = foldr del r $ map fst adrls
del :: FilePath -> Rule -> Rule
del t r@(pt, _, _)
| pt t = modifyFirstOfThree (&&& (/=t)) r
| otherwise = r
modifyFirstOfThree f (x, y, z) = (f x, y, z)
delRules :: [ Rule ] -> [ (FilePath, [FilePath]) ] -> [ Rule ]
delRules rls delrls = map dels rls
where
dels :: Rule -> Rule
dels r = foldr del r delrls
del :: (FilePath, [FilePath]) -> Rule -> Rule
del (t, ss) r@(pt, mkSs, _)
| pt t && isIncludedElem ss (mkSs t) = modifyFirstOfThree (&&& (/=t)) r
| otherwise = r
modifyFirstOfThree f (x, y, z) = (f x, y, z)
setCmd ::
Rule -> ( String -> [ String ] -> MadeFromList -> IO ExitCode ) -> Rule
setCmd (trgts, srcs, _) cmdsGen = (trgts, srcs, cmd)
where cmd :: Commands
cmd t s = do mfl <- asks snd
lift $ cmdsGen t s mfl `orDie` show
getVals :: String -> [String] -> [String]
getVals var args = maybe [] words $
dropUntil (=='=') <$> (listToMaybe $ filter (isPrefixOf $ var ++ "=") args)
getNewers :: FilePath -> [ FilePath ] -> IO [ FilePath ]
getNewers fb fs = catMaybes <$> mapM getNewer fs
where
getNewer :: FilePath -> IO (Maybe FilePath)
getNewer f = do
tb <- maybeGetModificationTime fb
t <- maybeGetModificationTime f
if (tb < t) then return $ Just f else return Nothing
base ::
Targets -> Sources
-> ( String -> [ String ] -> MadeFromList -> Bool -> IO ExitCode )
-> Rule
base trgts srcs cmdsGen = (trgts, srcs, cmd)
where cmd :: Commands
cmd t s = do mfl <- asks snd
us <- asks fst
lift $ cmdsGen t s mfl us `orDie` show
dflt :: [ String ] -> Rule
dflt trgts = ( (==defaultTrgtStr), const trgts, const2 $ return () )
deps :: [ String ] -> [ String ] -> Rule
deps trgts srcs
= ( \f -> or $ map (==f) trgts, const srcs, const2 $ return ())
mkfl :: String -> [ String ] -> Rule
mkfl trgt cont
= ( (==trgt), const [], \t -> const $ do
whenM (getUpdateStatus ||| lift (not <$> doesFileExist trgt)) $ do
lift $ putStrLn $ "make file `" ++ trgt ++ "' (hake)"
lift $ writeFile t $ unlines cont )