{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns, RecordWildCards, FlexibleInstances, TypeFamilies #-}
module Development.Shake.Internal.Rules.File(
need, needHasChanged, needBS, needed, neededBS, want,
trackRead, trackWrite, trackAllow,
defaultRuleFile,
(%>), (|%>), (?>), phony, (~>), phonys,
resultHasChanged,
FileQ(..), FileA, fileStoredValue, fileEqualValue, EqualCost(..), fileForward
) where
import Control.Applicative
import Control.Monad.Extra
import Control.Monad.IO.Class
import Data.Typeable
import Data.List
import Data.Maybe
import qualified Data.ByteString.Char8 as BS
import qualified Data.HashSet as Set
import Foreign.Storable
import Data.Word
import Data.Monoid
import General.Binary
import General.Extra
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Core.Run
import Development.Shake.Internal.Core.Action hiding (trackAllow)
import qualified Development.Shake.Internal.Core.Action as S
import Development.Shake.Internal.FileName
import Development.Shake.Internal.Rules.Rerun
import Development.Shake.Classes
import Development.Shake.FilePath(toStandard)
import Development.Shake.Internal.FilePattern
import Development.Shake.Internal.FileInfo
import Development.Shake.Internal.Options
import Development.Shake.Internal.Errors
import System.FilePath(takeDirectory)
import System.IO.Unsafe(unsafeInterleaveIO)
import Prelude
infix 1 %>, ?>, |%>, ~>
type instance RuleResult FileQ = FileR
newtype FileQ = FileQ {fromFileQ :: FileName}
deriving (Typeable,Eq,Hashable,Binary,BinaryEx,NFData)
data FileA = FileA {-# UNPACK #-} !ModTime {-# UNPACK #-} !FileSize FileHash
deriving (Typeable)
data FileR = FileR { result :: Maybe FileA
, hasChanged :: Bool
}
deriving (Typeable)
data Mode
= ModePhony (Action ())
| ModeDirect (Action ())
| ModeForward (Action (Maybe FileA))
data Result
= ResultPhony
| ResultDirect FileA
| ResultForward FileA
newtype FileRule = FileRule (FilePath -> Maybe Mode)
deriving Typeable
instance Show FileQ where show (FileQ x) = fileNameToString x
instance BinaryEx [FileQ] where
putEx = putEx . map fromFileQ
getEx = map FileQ . getEx
instance NFData FileA where
rnf (FileA a b c) = rnf a `seq` rnf b `seq` rnf c
instance NFData FileR where
rnf (FileR f b) = rnf f `seq` rnf b
instance Show FileA where
show (FileA m s h) = "File {mod=" ++ show m ++ ",size=" ++ show s ++ ",digest=" ++ show h ++ "}"
instance Show FileR where
show FileR{..} = show result ++ if hasChanged then " recomputed" else " not recomputed"
instance Storable FileA where
sizeOf _ = 4 * 3
alignment _ = alignment (undefined :: ModTime)
peekByteOff p i = FileA <$> peekByteOff p i <*> peekByteOff p (i+4) <*> peekByteOff p (i+8)
pokeByteOff p i (FileA a b c) = pokeByteOff p i a >> pokeByteOff p (i+4) b >> pokeByteOff p (i+8) c
instance BinaryEx FileA where
putEx = putExStorable
getEx = getExStorable
instance BinaryEx [FileA] where
putEx = putExStorableList
getEx = getExStorableList
fromResult :: Result -> Maybe FileA
fromResult ResultPhony = Nothing
fromResult (ResultDirect x) = Just x
fromResult (ResultForward x) = Just x
instance BinaryEx Result where
putEx ResultPhony = mempty
putEx (ResultDirect x) = putEx x
putEx (ResultForward x) = putEx (0 :: Word8) <> putEx x
getEx x = case BS.length x of
0 -> ResultPhony
12 -> ResultDirect $ getEx x
13 -> ResultForward $ getEx $ BS.tail x
data EqualCost
= EqualCheap
| EqualExpensive
| NotEqual
deriving (Eq,Ord,Show,Read,Typeable,Enum,Bounded)
fileStoredValue :: ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions{shakeChange=c} (FileQ x) = do
res <- getFileInfo x
case res of
Nothing -> return Nothing
Just (time,size) | c == ChangeModtime -> return $ Just $ FileA time size fileInfoNoHash
Just (time,size) -> do
hash <- unsafeInterleaveIO $ getFileHash x
return $ Just $ FileA time size hash
fileEqualValue :: ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions{shakeChange=c} (FileA x1 x2 x3) (FileA y1 y2 y3) = case c of
ChangeModtime -> bool $ x1 == y1
ChangeDigest -> bool $ x2 == y2 && x3 == y3
ChangeModtimeOrDigest -> bool $ x1 == y1 && x2 == y2 && x3 == y3
_ | x1 == y1 -> EqualCheap
| x2 == y2 && x3 == y3 -> EqualExpensive
| otherwise -> NotEqual
where bool b = if b then EqualCheap else NotEqual
storedValueError :: ShakeOptions -> Bool -> String -> FileQ -> IO (Maybe FileA)
storedValueError opts input msg x = maybe def Just <$> fileStoredValue opts2 x
where def = if shakeCreationCheck opts || input then error err else Nothing
err = msg ++ "\n " ++ fileNameToString (fromFileQ x)
opts2 = if not input && shakeChange opts == ChangeModtimeAndDigestInput then opts{shakeChange=ChangeModtime} else opts
defaultRuleFile :: Rules ()
defaultRuleFile = do
opts@ShakeOptions{..} <- getShakeOptionsRules
addBuiltinRuleEx (ruleLint opts) (ruleRun opts $ shakeRebuildApply opts)
ruleLint :: ShakeOptions -> BuiltinLint FileQ FileR
ruleLint opts k (FileR Nothing _) = return Nothing
ruleLint opts k (FileR (Just v) _) = do
now <- fileStoredValue opts k
return $ case now of
Nothing -> Just "<missing>"
Just now | fileEqualValue opts v now == EqualCheap -> Nothing
| otherwise -> Just $ show now
ruleRun :: ShakeOptions -> (FilePath -> Rebuild) -> BuiltinRun FileQ FileR
ruleRun opts@ShakeOptions{..} rebuildFlags o@(FileQ x) oldBin@(fmap getEx -> old) dirtyChildren = do
let r = rebuildFlags $ fileNameToString x
case old of
_ | r == RebuildNow -> rebuild
_ | r == RebuildLater -> case old of
Just old ->
unLint <$> retOld ChangedNothing
Nothing -> do
now <- liftIO $ fileStoredValue opts o
case now of
Nothing -> rebuild
Just now -> do alwaysRerun; retNew ChangedStore $ ResultDirect now
Just (ResultDirect old) | not dirtyChildren -> do
now <- liftIO $ fileStoredValue opts o
case now of
Nothing -> rebuild
Just now -> case fileEqualValue opts old now of
EqualCheap -> retNew ChangedNothing $ ResultDirect now
EqualExpensive -> retNew ChangedStore $ ResultDirect now
NotEqual -> rebuild
Just (ResultForward old) | not dirtyChildren -> retOld ChangedNothing
_ -> rebuild
where
asLint (ResultDirect x) = Just x
asLint x = Nothing
unLint (RunResult a b (FileR _ c)) = RunResult a b $ FileR Nothing c
retNew :: RunChanged -> Result -> Action (RunResult FileR)
retNew c v = return $ RunResult c (runBuilder $ putEx v) (FileR (asLint v) (c == ChangedRecomputeDiff))
retOld :: RunChanged -> Action (RunResult FileR)
retOld c = return $ RunResult c (fromJust oldBin) $ FileR (asLint $ fromJust old) False
rebuild = do
putWhen Chatty $ "# " ++ show o
x <- return $ fileNameToString x
rules <- getUserRules
act <- case userRuleMatch rules $ \(FileRule f) -> f x of
[] -> return Nothing
[r] -> return $ Just r
rs -> liftIO $ errorMultipleRulesMatch (typeOf o) (show o) (length rs)
let answer ctor new = do
let b = case () of
_ | Just old <- old
, Just old <- fromResult old
, fileEqualValue opts old new /= NotEqual -> ChangedRecomputeSame
_ -> ChangedRecomputeDiff
retNew b $ ctor new
case act of
Nothing -> do
new <- liftIO $ storedValueError opts True "Error, file does not exist and no rule available:" o
answer ResultDirect $ fromJust new
Just (ModeForward act) -> do
new <- act
case new of
Nothing -> do
alwaysRerun
retNew ChangedRecomputeDiff ResultPhony
Just new -> answer ResultForward new
Just (ModeDirect act) -> do
act
new <- liftIO $ storedValueError opts False "Error, rule finished running but did not produce file:" o
case new of
Nothing -> retNew ChangedRecomputeDiff ResultPhony
Just new -> answer ResultDirect new
Just (ModePhony act) -> do
alwaysRerun
act
retNew ChangedRecomputeDiff ResultPhony
apply_ :: (a -> FileName) -> [a] -> Action [FileR]
apply_ f = apply . map (FileQ . f)
resultHasChanged :: FilePath -> Action Bool
resultHasChanged file = do
let filename = FileQ $ fileNameFromString file
res <- getDatabaseValue filename
old <- return $ case res of
Nothing -> Nothing
Just (Left bs) -> fromResult $ getEx bs
Just (Right v) -> result v
case old of
Nothing -> return True
Just old -> do
opts <- getShakeOptions
new <- liftIO $ fileStoredValue opts filename
return $ case new of
Nothing -> True
Just new -> fileEqualValue opts old new == NotEqual
fileForward :: (FilePath -> Maybe (Action (Maybe FileA))) -> Rules ()
fileForward act = addUserRule $ FileRule $ fmap ModeForward . act
need :: [FilePath] -> Action ()
need = void . apply_ fileNameFromString
needHasChanged :: [FilePath] -> Action [FilePath]
needHasChanged paths = do
res <- apply_ fileNameFromString paths
return [a | (a,b) <- zip paths res, hasChanged b]
needBS :: [BS.ByteString] -> Action ()
needBS = void . apply_ fileNameFromByteString
needed :: [FilePath] -> Action ()
needed xs = do
opts <- getShakeOptions
if isNothing $ shakeLint opts then need xs else neededCheck $ map fileNameFromString xs
neededBS :: [BS.ByteString] -> Action ()
neededBS xs = do
opts <- getShakeOptions
if isNothing $ shakeLint opts then needBS xs else neededCheck $ map fileNameFromByteString xs
neededCheck :: [FileName] -> Action ()
neededCheck xs = do
opts <- getShakeOptions
pre <- liftIO $ mapM (fileStoredValue opts . FileQ) xs
post <- apply_ id xs
let bad = [ (x, if isJust a then "File change" else "File created")
| (x, a, FileR (Just b) _) <- zip3 xs pre post, maybe NotEqual (\a -> fileEqualValue opts a b) a == NotEqual]
case bad of
[] -> return ()
(file,msg):_ -> liftIO $ errorStructured
"Lint checking error - 'needed' file required rebuilding"
[("File", Just $ fileNameToString file)
,("Error",Just msg)]
""
trackRead :: [FilePath] -> Action ()
trackRead = mapM_ (trackUse . FileQ . fileNameFromString)
trackWrite :: [FilePath] -> Action ()
trackWrite = mapM_ (trackChange . FileQ . fileNameFromString)
trackAllow :: [FilePattern] -> Action ()
trackAllow ps = do
opts <- getShakeOptions
when (isJust $ shakeLint opts) $
S.trackAllow $ \(FileQ x) -> any (?== fileNameToString x) ps
want :: [FilePath] -> Rules ()
want [] = return ()
want xs = action $ need xs
root :: String -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root help test act = addUserRule $ FileRule $ \x -> if not $ test x then Nothing else Just $ ModeDirect $ do
liftIO $ createDirectoryRecursive $ takeDirectory x
act x
phony :: String -> Action () -> Rules ()
phony (toStandard -> name) act = phonys $ \s -> if s == name then Just act else Nothing
phonys :: (String -> Maybe (Action ())) -> Rules ()
phonys act = addUserRule $ FileRule $ fmap ModePhony . act
(~>) :: String -> Action () -> Rules ()
(~>) = phony
(?>) :: (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
(?>) test act = priority 0.5 $ root "with ?>" test act
(|%>) :: [FilePattern] -> (FilePath -> Action ()) -> Rules ()
(|%>) pats act = do
let (simp,other) = partition simple pats
case simp of
[] -> return ()
[p] -> let pp = toStandard p in root "with |%>" (\x -> toStandard x == pp) act
ps -> let ps = Set.fromList $ map toStandard pats in root "with |%>" (flip Set.member ps . toStandard) act
unless (null other) $
let ps = map (?==) other in priority 0.5 $ root "with |%>" (\x -> any ($ x) ps) act
(%>) :: FilePattern -> (FilePath -> Action ()) -> Rules ()
(%>) test act = (if simple test then id else priority 0.5) $ root (show test) (test ?==) act