module Development.Shake.Util(
parseMakefile, needMakefileDependencies, neededMakefileDependencies,
shakeArgsAccumulate, shakeArgsPrune, shakeArgsPruneWith,
) where
import Development.Shake
import Development.Shake.Internal.Rules.File
import qualified Data.ByteString.Char8 as BS
import qualified General.Makefile as BS
import Data.Tuple.Extra
import Data.List
import General.GetOpt
import Data.IORef
import Data.Maybe
import Control.Monad.Extra
import System.IO.Extra as IO
parseMakefile :: String -> [(FilePath, [FilePath])]
parseMakefile = map (BS.unpack *** map BS.unpack) . BS.parseMakefile . BS.pack
needMakefileDependencies :: FilePath -> Action ()
needMakefileDependencies file = needBS . concatMap snd . BS.parseMakefile =<< liftIO (BS.readFile file)
neededMakefileDependencies :: FilePath -> Action ()
neededMakefileDependencies file = neededBS . concatMap snd . BS.parseMakefile =<< liftIO (BS.readFile file)
shakeArgsAccumulate :: ShakeOptions -> [OptDescr (Either String (a -> a))] -> a -> (a -> [String] -> IO (Maybe (Rules ()))) -> IO ()
shakeArgsAccumulate opts flags def f = shakeArgsWith opts flags $ \flags targets -> f (foldl' (flip ($)) def flags) targets
shakeArgsPrune :: ShakeOptions -> ([FilePath] -> IO ()) -> Rules () -> IO ()
shakeArgsPrune opts prune rules = shakeArgsPruneWith opts prune [] f
where f _ files = return $ Just $ if null files then rules else want files >> withoutActions rules
shakeArgsPruneWith :: ShakeOptions -> ([FilePath] -> IO ()) -> [OptDescr (Either String a)] -> ([a] -> [String] -> IO (Maybe (Rules ()))) -> IO ()
shakeArgsPruneWith opts prune flags act = do
let flags2 = Option "P" ["prune"] (NoArg $ Right Nothing) "Remove stale files" : map (fmapFmapOptDescr Just) flags
pruning <- newIORef False
shakeArgsWith opts flags2 $ \opts args ->
case sequence opts of
Nothing -> do
writeIORef pruning True
return Nothing
Just opts -> act opts args
whenM (readIORef pruning) $
IO.withTempFile $ \file -> do
shakeArgsWith opts{shakeLiveFiles=file : shakeLiveFiles opts} flags2 $ \opts args ->
act (catMaybes opts) args
src <- lines <$> IO.readFile' file
prune src