{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
module Development.Shake.Internal.Rules.Directory(
doesFileExist, doesDirectoryExist,
getDirectoryContents, getDirectoryFiles, getDirectoryDirs,
getEnv, getEnvWithDefault,
removeFiles, removeFilesAfter,
getDirectoryFilesIO,
defaultRuleDirectory
) where
import Control.Monad.Extra
import Control.Monad.IO.Class
import Data.Maybe
import Data.Binary
import Data.List
import Data.Tuple.Extra
import qualified Data.HashSet as Set
import qualified System.Directory as IO
import qualified System.Environment as IO
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Action
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Core.Build
import Development.Shake.Internal.Value
import Development.Shake.Classes
import Development.Shake.FilePath
import Development.Shake.Internal.FilePattern
import General.Extra
import General.Binary
type instance RuleResult DoesFileExistQ = DoesFileExistA
newtype DoesFileExistQ = DoesFileExistQ FilePath
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show DoesFileExistQ where
show (DoesFileExistQ a) = "doesFileExist " ++ wrapQuote a
newtype DoesFileExistA = DoesFileExistA {fromDoesFileExistA :: Bool}
deriving (Typeable,Eq,BinaryEx,NFData)
instance Show DoesFileExistA where
show (DoesFileExistA a) = show a
type instance RuleResult DoesDirectoryExistQ = DoesDirectoryExistA
newtype DoesDirectoryExistQ = DoesDirectoryExistQ FilePath
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show DoesDirectoryExistQ where
show (DoesDirectoryExistQ a) = "doesDirectoryExist " ++ wrapQuote a
newtype DoesDirectoryExistA = DoesDirectoryExistA {fromDoesDirectoryExistA :: Bool}
deriving (Typeable,Eq,BinaryEx,NFData)
instance Show DoesDirectoryExistA where
show (DoesDirectoryExistA a) = show a
type instance RuleResult GetEnvQ = GetEnvA
newtype GetEnvQ = GetEnvQ String
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show GetEnvQ where
show (GetEnvQ a) = "getEnv " ++ wrapQuote a
newtype GetEnvA = GetEnvA {fromGetEnvA :: Maybe String}
deriving (Typeable,Eq,Hashable,BinaryEx,NFData)
instance Show GetEnvA where
show (GetEnvA a) = maybe "<unset>" wrapQuote a
type instance RuleResult GetDirectoryContentsQ = GetDirectoryA
type instance RuleResult GetDirectoryFilesQ = GetDirectoryA
type instance RuleResult GetDirectoryDirsQ = GetDirectoryA
newtype GetDirectoryContentsQ = GetDirectoryContentsQ FilePath
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show GetDirectoryContentsQ where
show (GetDirectoryContentsQ dir) = "getDirectoryContents " ++ wrapQuote dir
newtype GetDirectoryFilesQ = GetDirectoryFilesQ (FilePath, [FilePattern])
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show GetDirectoryFilesQ where
show (GetDirectoryFilesQ (dir, pat)) = "getDirectoryFiles " ++ wrapQuote dir ++ " [" ++ unwords (map wrapQuote pat) ++ "]"
newtype GetDirectoryDirsQ = GetDirectoryDirsQ FilePath
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
instance Show GetDirectoryDirsQ where
show (GetDirectoryDirsQ dir) = "getDirectoryDirs " ++ wrapQuote dir
newtype GetDirectoryA = GetDirectoryA {fromGetDirectoryA :: [FilePath]}
deriving (Typeable,Eq,Hashable,BinaryEx,NFData)
instance Show GetDirectoryA where
show (GetDirectoryA xs) = unwords $ map wrapQuote xs
queryRule :: (RuleResult key ~ value
,BinaryEx witness, Eq witness
,BinaryEx key, ShakeValue key
,Typeable value, NFData value, Show value, Eq value)
=> (value -> witness) -> (key -> IO value) -> Rules ()
queryRule witness query = addBuiltinRuleEx
(\k old -> do
new <- query k
return $ if old == new then Nothing else Just $ show new)
(\_ v -> Just $ runBuilder $ putEx $ witness v)
(\k old _ -> liftIO $ do
new <- query k
let wnew = witness new
return $ case old of
Just old | wnew == getEx old -> RunResult ChangedNothing old new
_ -> RunResult ChangedRecomputeDiff (runBuilder $ putEx wnew) new)
defaultRuleDirectory :: Rules ()
defaultRuleDirectory = do
queryRule id (\(DoesFileExistQ x) -> DoesFileExistA <$> IO.doesFileExist x)
queryRule id (\(DoesDirectoryExistQ x) -> DoesDirectoryExistA <$> IO.doesDirectoryExist x)
queryRule hash (\(GetEnvQ x) -> GetEnvA <$> IO.lookupEnv x)
queryRule hash (\(GetDirectoryContentsQ x) -> GetDirectoryA <$> getDirectoryContentsIO x)
queryRule hash (\(GetDirectoryFilesQ (a,b)) -> GetDirectoryA <$> getDirectoryFilesIO a b)
queryRule hash (\(GetDirectoryDirsQ x) -> GetDirectoryA <$> getDirectoryDirsIO x)
doesFileExist :: FilePath -> Action Bool
doesFileExist = fmap fromDoesFileExistA . apply1 . DoesFileExistQ . toStandard
doesDirectoryExist :: FilePath -> Action Bool
doesDirectoryExist = fmap fromDoesDirectoryExistA . apply1 . DoesDirectoryExistQ . toStandard
getEnv :: String -> Action (Maybe String)
getEnv = fmap fromGetEnvA . apply1 . GetEnvQ
getEnvWithDefault :: String -> String -> Action String
getEnvWithDefault def var = fromMaybe def <$> getEnv var
getDirectoryContents :: FilePath -> Action [FilePath]
getDirectoryContents = fmap fromGetDirectoryA . apply1 . GetDirectoryContentsQ
getDirectoryFiles :: FilePath -> [FilePattern] -> Action [FilePath]
getDirectoryFiles dir pat = fmap fromGetDirectoryA $ apply1 $ GetDirectoryFilesQ (dir,pat)
getDirectoryDirs :: FilePath -> Action [FilePath]
getDirectoryDirs = fmap fromGetDirectoryA . apply1 . GetDirectoryDirsQ
getDirectoryContentsIO :: FilePath -> IO [FilePath]
getDirectoryContentsIO dir = fmap (sort . filter (not . all (== '.'))) $ IO.getDirectoryContents $ if dir == "" then "." else dir
getDirectoryDirsIO :: FilePath -> IO [FilePath]
getDirectoryDirsIO dir = filterM f =<< getDirectoryContentsIO dir
where f x = IO.doesDirectoryExist $ dir </> x
getDirectoryFilesIO :: FilePath -> [FilePattern] -> IO [FilePath]
getDirectoryFilesIO root pat = f "" $ snd $ walk pat
where
f dir (Walk op) = f dir . WalkTo . op =<< getDirectoryContentsIO (root </> dir)
f dir (WalkTo (files, dirs)) = do
files <- filterM (IO.doesFileExist . (root </>)) $ map (dir </>) files
dirs <- concatMapM (uncurry f) =<< filterM (IO.doesDirectoryExist . (root </>) . fst) (map (first (dir </>)) dirs)
return $ files ++ dirs
removeFiles :: FilePath -> [FilePattern] -> IO ()
removeFiles dir pat =
whenM (IO.doesDirectoryExist dir) $ do
let (b,w) = walk pat
if b then removeDir dir else f dir w
where
f dir (Walk op) = f dir . WalkTo . op =<< getDirectoryContentsIO dir
f dir (WalkTo (files, dirs)) = do
forM_ files $ \fil ->
tryIO $ removeItem $ dir </> fil
let done = Set.fromList files
forM_ (filter (not . flip Set.member done . fst) dirs) $ \(d,w) -> do
let dir2 = dir </> d
whenM (IO.doesDirectoryExist dir2) $ f dir2 w
removeItem :: FilePath -> IO ()
removeItem x = IO.removeFile x `catchIO` \_ -> removeDir x
removeDir :: FilePath -> IO ()
removeDir x = do
mapM_ (removeItem . (x </>)) =<< getDirectoryContentsIO x
IO.removeDirectory x
removeFilesAfter :: FilePath -> [FilePattern] -> Action ()
removeFilesAfter a b = do
putLoud $ "Will remove " ++ unwords b ++ " from " ++ a
runAfter $ removeFiles a b