{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, ScopedTypeVariables, NamedFieldPuns #-}
{-# LANGUAGE ViewPatterns, RecordWildCards, FlexibleInstances, TypeFamilies, ConstraintKinds #-}

module Development.Shake.Internal.Rules.File(
    need, needHasChanged, needBS, needed, neededBS, want,
    trackRead, trackWrite, trackAllow, produces,
    defaultRuleFile,
    (%>), (|%>), (?>), phony, (~>), phonys,
    resultHasChanged,
    -- * Internal only
    FileQ(..), FileA(..), fileStoredValue, fileEqualValue, EqualCost(..), fileForward
    ) where

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.Build
import Development.Shake.Internal.Core.Action
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) -- important that this is the system local filepath, or wrong slashes go wrong
import System.IO.Unsafe(unsafeInterleaveIO)

import Prelude


infix 1 %>, ?>, |%>, ~>

---------------------------------------------------------------------
-- TYPES

type instance RuleResult FileQ = FileR

-- | The unique key we use to index File rules, to avoid name clashes.
newtype FileQ = FileQ {FileQ -> FileName
fromFileQ :: FileName}
    deriving (Typeable,FileQ -> FileQ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileQ -> FileQ -> Bool
$c/= :: FileQ -> FileQ -> Bool
== :: FileQ -> FileQ -> Bool
$c== :: FileQ -> FileQ -> Bool
Eq,Eq FileQ
Int -> FileQ -> Int
FileQ -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FileQ -> Int
$chash :: FileQ -> Int
hashWithSalt :: Int -> FileQ -> Int
$chashWithSalt :: Int -> FileQ -> Int
Hashable,Get FileQ
[FileQ] -> Put
FileQ -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [FileQ] -> Put
$cputList :: [FileQ] -> Put
get :: Get FileQ
$cget :: Get FileQ
put :: FileQ -> Put
$cput :: FileQ -> Put
Binary,ByteString -> FileQ
FileQ -> Builder
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> FileQ
$cgetEx :: ByteString -> FileQ
putEx :: FileQ -> Builder
$cputEx :: FileQ -> Builder
BinaryEx,FileQ -> ()
forall a. (a -> ()) -> NFData a
rnf :: FileQ -> ()
$crnf :: FileQ -> ()
NFData)

-- | Raw information about a file.
data FileA = FileA {-# UNPACK #-} !ModTime {-# UNPACK #-} !FileSize FileHash
    deriving (Typeable)

-- | Result of a File rule, may contain raw file information and whether the rule did run this build
data FileR = FileR { FileR -> Maybe FileA
answer :: !(Maybe FileA) -- ^ Raw information about the file built by this rule.
                                              --   Set to 'Nothing' for 'phony' files.
                   , FileR -> Bool
useLint :: !Bool       -- ^ Should we lint the resulting file
                   }
    deriving (Typeable)

-- | The types of file rule that occur.
data Mode
    = ModePhony (Action ()) -- ^ An action with no file value
    | ModeDirect (Action ()) -- ^ An action that produces this file
    | ModeForward (Action (Maybe FileA)) -- ^ An action that looks up a file someone else produced

-- | The results of the various 'Mode' rules.
data Answer
    = AnswerPhony
    | AnswerDirect Ver FileA
    | AnswerForward Ver FileA

-- | The file rules we use, first is the name (as pretty as you can get).
data FileRule = FileRule String (FilePath -> Maybe Mode)
    deriving Typeable


---------------------------------------------------------------------
-- INSTANCES

instance Show FileQ where show :: FileQ -> FilePath
show (FileQ FileName
x) = FileName -> FilePath
fileNameToString FileName
x

instance BinaryEx [FileQ] where
    putEx :: [FileQ] -> Builder
putEx = forall a. BinaryEx a => a -> Builder
putEx forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map FileQ -> FileName
fromFileQ
    getEx :: ByteString -> [FileQ]
getEx = forall a b. (a -> b) -> [a] -> [b]
map FileName -> FileQ
FileQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. BinaryEx a => ByteString -> a
getEx

instance NFData FileA where
    rnf :: FileA -> ()
rnf (FileA ModTime
a FileSize
b FileHash
c) = forall a. NFData a => a -> ()
rnf ModTime
a seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf FileSize
b seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf FileHash
c

instance NFData FileR where
    rnf :: FileR -> ()
rnf (FileR Maybe FileA
a Bool
b) = forall a. NFData a => a -> ()
rnf Maybe FileA
a seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Bool
b

instance Show FileA where
    show :: FileA -> FilePath
show (FileA ModTime
m FileSize
s FileHash
h) = FilePath
"File {mod=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show ModTime
m forall a. [a] -> [a] -> [a]
++ FilePath
",size=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FileSize
s forall a. [a] -> [a] -> [a]
++ FilePath
",digest=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FileHash
h forall a. [a] -> [a] -> [a]
++ FilePath
"}"

instance Show FileR where
    show :: FileR -> FilePath
show FileR{Bool
Maybe FileA
useLint :: Bool
answer :: Maybe FileA
useLint :: FileR -> Bool
answer :: FileR -> Maybe FileA
..} = forall a. Show a => a -> FilePath
show Maybe FileA
answer

instance Storable FileA where
    sizeOf :: FileA -> Int
sizeOf FileA
_ = Int
4 forall a. Num a => a -> a -> a
* Int
3 -- 4 Word32's
    alignment :: FileA -> Int
alignment FileA
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined :: ModTime)
    peekByteOff :: forall b. Ptr b -> Int -> IO FileA
peekByteOff Ptr b
p Int
i = ModTime -> FileSize -> FileHash -> FileA
FileA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
i forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
iforall a. Num a => a -> a -> a
+Int
4) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
iforall a. Num a => a -> a -> a
+Int
8)
    pokeByteOff :: forall b. Ptr b -> Int -> FileA -> IO ()
pokeByteOff Ptr b
p Int
i (FileA ModTime
a FileSize
b FileHash
c) = forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p Int
i ModTime
a forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
iforall a. Num a => a -> a -> a
+Int
4) FileSize
b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
iforall a. Num a => a -> a -> a
+Int
8) FileHash
c

instance BinaryEx FileA where
    putEx :: FileA -> Builder
putEx = forall a. Storable a => a -> Builder
putExStorable
    getEx :: ByteString -> FileA
getEx = forall a. Storable a => ByteString -> a
getExStorable

instance BinaryEx [FileA] where
    putEx :: [FileA] -> Builder
putEx = forall a. Storable a => [a] -> Builder
putExStorableList
    getEx :: ByteString -> [FileA]
getEx = forall a. Storable a => ByteString -> [a]
getExStorableList

fromAnswer :: Answer -> Maybe FileA
fromAnswer :: Answer -> Maybe FileA
fromAnswer Answer
AnswerPhony = forall a. Maybe a
Nothing
fromAnswer (AnswerDirect Ver
_ FileA
x) = forall a. a -> Maybe a
Just FileA
x
fromAnswer (AnswerForward Ver
_ FileA
x) = forall a. a -> Maybe a
Just FileA
x

instance BinaryEx Answer where
    putEx :: Answer -> Builder
putEx Answer
AnswerPhony = forall a. Monoid a => a
mempty
    putEx (AnswerDirect Ver
ver FileA
x) = forall a. Storable a => a -> Builder
putExStorable Ver
ver forall a. Semigroup a => a -> a -> a
<> forall a. BinaryEx a => a -> Builder
putEx FileA
x
    putEx (AnswerForward Ver
ver FileA
x) = forall a. BinaryEx a => a -> Builder
putEx (Word8
0 :: Word8) forall a. Semigroup a => a -> a -> a
<> forall a. Storable a => a -> Builder
putExStorable Ver
ver forall a. Semigroup a => a -> a -> a
<> forall a. BinaryEx a => a -> Builder
putEx FileA
x

    getEx :: ByteString -> Answer
getEx ByteString
x = case ByteString -> Int
BS.length ByteString
x of
        Int
0 -> Answer
AnswerPhony
        Int
i -> if Int
i forall a. Eq a => a -> a -> Bool
== Int
sz then forall {t} {a} {b}.
(Storable t, BinaryEx a) =>
(t -> a -> b) -> ByteString -> b
f Ver -> FileA -> Answer
AnswerDirect ByteString
x else forall {t} {a} {b}.
(Storable t, BinaryEx a) =>
(t -> a -> b) -> ByteString -> b
f Ver -> FileA -> Answer
AnswerForward forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail ByteString
x
        where
            sz :: Int
sz = forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Ver) forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: FileA)
            f :: (t -> a -> b) -> ByteString -> b
f t -> a -> b
ctor ByteString
x = let (t
a,ByteString
b) = forall a. Storable a => ByteString -> (a, ByteString)
binarySplit ByteString
x in t -> a -> b
ctor t
a forall a b. (a -> b) -> a -> b
$ forall a. BinaryEx a => ByteString -> a
getEx ByteString
b


---------------------------------------------------------------------
-- FILE CHECK QUERIES

-- | An equality check and a cost.
data EqualCost
    = EqualCheap -- ^ The equality check was cheap.
    | EqualExpensive -- ^ The equality check was expensive, as the results are not trivially equal.
    | NotEqual -- ^ The values are not equal.
      deriving (EqualCost -> EqualCost -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EqualCost -> EqualCost -> Bool
$c/= :: EqualCost -> EqualCost -> Bool
== :: EqualCost -> EqualCost -> Bool
$c== :: EqualCost -> EqualCost -> Bool
Eq,Eq EqualCost
EqualCost -> EqualCost -> Bool
EqualCost -> EqualCost -> Ordering
EqualCost -> EqualCost -> EqualCost
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EqualCost -> EqualCost -> EqualCost
$cmin :: EqualCost -> EqualCost -> EqualCost
max :: EqualCost -> EqualCost -> EqualCost
$cmax :: EqualCost -> EqualCost -> EqualCost
>= :: EqualCost -> EqualCost -> Bool
$c>= :: EqualCost -> EqualCost -> Bool
> :: EqualCost -> EqualCost -> Bool
$c> :: EqualCost -> EqualCost -> Bool
<= :: EqualCost -> EqualCost -> Bool
$c<= :: EqualCost -> EqualCost -> Bool
< :: EqualCost -> EqualCost -> Bool
$c< :: EqualCost -> EqualCost -> Bool
compare :: EqualCost -> EqualCost -> Ordering
$ccompare :: EqualCost -> EqualCost -> Ordering
Ord,Int -> EqualCost -> ShowS
[EqualCost] -> ShowS
EqualCost -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [EqualCost] -> ShowS
$cshowList :: [EqualCost] -> ShowS
show :: EqualCost -> FilePath
$cshow :: EqualCost -> FilePath
showsPrec :: Int -> EqualCost -> ShowS
$cshowsPrec :: Int -> EqualCost -> ShowS
Show,ReadPrec [EqualCost]
ReadPrec EqualCost
Int -> ReadS EqualCost
ReadS [EqualCost]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EqualCost]
$creadListPrec :: ReadPrec [EqualCost]
readPrec :: ReadPrec EqualCost
$creadPrec :: ReadPrec EqualCost
readList :: ReadS [EqualCost]
$creadList :: ReadS [EqualCost]
readsPrec :: Int -> ReadS EqualCost
$creadsPrec :: Int -> ReadS EqualCost
Read,Typeable,Int -> EqualCost
EqualCost -> Int
EqualCost -> [EqualCost]
EqualCost -> EqualCost
EqualCost -> EqualCost -> [EqualCost]
EqualCost -> EqualCost -> EqualCost -> [EqualCost]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: EqualCost -> EqualCost -> EqualCost -> [EqualCost]
$cenumFromThenTo :: EqualCost -> EqualCost -> EqualCost -> [EqualCost]
enumFromTo :: EqualCost -> EqualCost -> [EqualCost]
$cenumFromTo :: EqualCost -> EqualCost -> [EqualCost]
enumFromThen :: EqualCost -> EqualCost -> [EqualCost]
$cenumFromThen :: EqualCost -> EqualCost -> [EqualCost]
enumFrom :: EqualCost -> [EqualCost]
$cenumFrom :: EqualCost -> [EqualCost]
fromEnum :: EqualCost -> Int
$cfromEnum :: EqualCost -> Int
toEnum :: Int -> EqualCost
$ctoEnum :: Int -> EqualCost
pred :: EqualCost -> EqualCost
$cpred :: EqualCost -> EqualCost
succ :: EqualCost -> EqualCost
$csucc :: EqualCost -> EqualCost
Enum,EqualCost
forall a. a -> a -> Bounded a
maxBound :: EqualCost
$cmaxBound :: EqualCost
minBound :: EqualCost
$cminBound :: EqualCost
Bounded)

fileStoredValue :: ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue :: ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions{shakeChange :: ShakeOptions -> Change
shakeChange=Change
c, shakeNeedDirectory :: ShakeOptions -> Bool
shakeNeedDirectory=Bool
allowDir} (FileQ FileName
x) = do
    Maybe (ModTime, FileSize)
res <- Bool -> FileName -> IO (Maybe (ModTime, FileSize))
getFileInfo Bool
allowDir FileName
x
    case Maybe (ModTime, FileSize)
res of
        Maybe (ModTime, FileSize)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
        Just (ModTime
time,FileSize
size) | Change
c forall a. Eq a => a -> a -> Bool
== Change
ChangeModtime -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ModTime -> FileSize -> FileHash -> FileA
FileA ModTime
time FileSize
size FileHash
noFileHash
        Just (ModTime
time,FileSize
size) -> do
            FileHash
hash <- forall a. IO a -> IO a
unsafeInterleaveIO forall a b. (a -> b) -> a -> b
$ FileName -> IO FileHash
getFileHash FileName
x
            forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ModTime -> FileSize -> FileHash -> FileA
FileA ModTime
time FileSize
size FileHash
hash


fileEqualValue :: ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue :: ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions{shakeChange :: ShakeOptions -> Change
shakeChange=Change
c} (FileA ModTime
x1 FileSize
x2 FileHash
x3) (FileA ModTime
y1 FileSize
y2 FileHash
y3) = case Change
c of
    Change
ChangeModtime -> Bool -> EqualCost
bool forall a b. (a -> b) -> a -> b
$ ModTime
x1 forall a. Eq a => a -> a -> Bool
== ModTime
y1
    Change
ChangeDigest -> Bool -> EqualCost
bool forall a b. (a -> b) -> a -> b
$ FileSize
x2 forall a. Eq a => a -> a -> Bool
== FileSize
y2 Bool -> Bool -> Bool
&& FileHash
x3 forall a. Eq a => a -> a -> Bool
== FileHash
y3
    Change
ChangeModtimeOrDigest -> Bool -> EqualCost
bool forall a b. (a -> b) -> a -> b
$ ModTime
x1 forall a. Eq a => a -> a -> Bool
== ModTime
y1 Bool -> Bool -> Bool
&& FileSize
x2 forall a. Eq a => a -> a -> Bool
== FileSize
y2 Bool -> Bool -> Bool
&& FileHash
x3 forall a. Eq a => a -> a -> Bool
== FileHash
y3
    Change
_ | ModTime
x1 forall a. Eq a => a -> a -> Bool
== ModTime
y1 -> EqualCost
EqualCheap
      | FileSize
x2 forall a. Eq a => a -> a -> Bool
== FileSize
y2 Bool -> Bool -> Bool
&& FileHash
x3 forall a. Eq a => a -> a -> Bool
== FileHash
y3 -> EqualCost
EqualExpensive
      | Bool
otherwise -> EqualCost
NotEqual
    where bool :: Bool -> EqualCost
bool Bool
b = if Bool
b then EqualCost
EqualCheap else EqualCost
NotEqual


-- | Arguments: options; is the file an input; a message for failure if the file does not exist; filename
storedValueError :: ShakeOptions -> Bool -> String -> FileQ -> IO (Maybe FileA)
{-
storedValueError opts False msg x | False && not (shakeOutputCheck opts) = do
    when (shakeCreationCheck opts) $ do
        whenM (isNothing <$> (storedValue opts x :: IO (Maybe FileA))) $ error $ msg ++ "\n  " ++ unpackU (fromFileQ x)
    pure $ FileA fileInfoEq fileInfoEq fileInfoEq
-}
storedValueError :: ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA)
storedValueError ShakeOptions
opts Bool
input FilePath
msg FileQ
x = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe FileA
def forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts2 FileQ
x
    where def :: Maybe FileA
def = if ShakeOptions -> Bool
shakeCreationCheck ShakeOptions
opts Bool -> Bool -> Bool
|| Bool
input then forall a. HasCallStack => FilePath -> a
error FilePath
err else forall a. Maybe a
Nothing
          err :: FilePath
err = FilePath
msg forall a. [a] -> [a] -> [a]
++ FilePath
"\n  " forall a. [a] -> [a] -> [a]
++ FileName -> FilePath
fileNameToString (FileQ -> FileName
fromFileQ FileQ
x)
          opts2 :: ShakeOptions
opts2 = if Bool -> Bool
not Bool
input Bool -> Bool -> Bool
&& ShakeOptions -> Change
shakeChange ShakeOptions
opts forall a. Eq a => a -> a -> Bool
== Change
ChangeModtimeAndDigestInput then ShakeOptions
opts{shakeChange :: Change
shakeChange=Change
ChangeModtime} else ShakeOptions
opts


---------------------------------------------------------------------
-- THE DEFAULT RULE

defaultRuleFile :: Rules ()
defaultRuleFile :: Rules ()
defaultRuleFile = do
    opts :: ShakeOptions
opts@ShakeOptions{Bool
Int
FilePath
[FilePath]
[(FilePath, FilePath)]
[(Rebuild, FilePath)]
[CmdOption]
Maybe Seconds
Maybe FilePath
Maybe Lint
HashMap TypeRep Dynamic
Verbosity
Change
FilePath -> FilePath -> Bool -> IO ()
IO Progress -> IO ()
Verbosity -> FilePath -> IO ()
shakeExtra :: ShakeOptions -> HashMap TypeRep Dynamic
shakeTrace :: ShakeOptions -> FilePath -> FilePath -> Bool -> IO ()
shakeOutput :: ShakeOptions -> Verbosity -> FilePath -> IO ()
shakeProgress :: ShakeOptions -> IO Progress -> IO ()
shakeAllowRedefineRules :: ShakeOptions -> Bool
shakeSymlink :: ShakeOptions -> Bool
shakeCloud :: ShakeOptions -> [FilePath]
shakeShare :: ShakeOptions -> Maybe FilePath
shakeColor :: ShakeOptions -> Bool
shakeVersionIgnore :: ShakeOptions -> Bool
shakeLiveFiles :: ShakeOptions -> [FilePath]
shakeRunCommands :: ShakeOptions -> Bool
shakeTimings :: ShakeOptions -> Bool
shakeLineBuffering :: ShakeOptions -> Bool
shakeStorageLog :: ShakeOptions -> Bool
shakeAbbreviations :: ShakeOptions -> [(FilePath, FilePath)]
shakeRebuild :: ShakeOptions -> [(Rebuild, FilePath)]
shakeFlush :: ShakeOptions -> Maybe Seconds
shakeCommandOptions :: ShakeOptions -> [CmdOption]
shakeLintWatch :: ShakeOptions -> [FilePath]
shakeLintIgnore :: ShakeOptions -> [FilePath]
shakeLintInside :: ShakeOptions -> [FilePath]
shakeLint :: ShakeOptions -> Maybe Lint
shakeReport :: ShakeOptions -> [FilePath]
shakeStaunch :: ShakeOptions -> Bool
shakeVerbosity :: ShakeOptions -> Verbosity
shakeVersion :: ShakeOptions -> FilePath
shakeThreads :: ShakeOptions -> Int
shakeFiles :: ShakeOptions -> FilePath
shakeExtra :: HashMap TypeRep Dynamic
shakeTrace :: FilePath -> FilePath -> Bool -> IO ()
shakeOutput :: Verbosity -> FilePath -> IO ()
shakeProgress :: IO Progress -> IO ()
shakeAllowRedefineRules :: Bool
shakeNeedDirectory :: Bool
shakeSymlink :: Bool
shakeCloud :: [FilePath]
shakeShare :: Maybe FilePath
shakeColor :: Bool
shakeVersionIgnore :: Bool
shakeLiveFiles :: [FilePath]
shakeCreationCheck :: Bool
shakeChange :: Change
shakeRunCommands :: Bool
shakeTimings :: Bool
shakeLineBuffering :: Bool
shakeStorageLog :: Bool
shakeAbbreviations :: [(FilePath, FilePath)]
shakeRebuild :: [(Rebuild, FilePath)]
shakeFlush :: Maybe Seconds
shakeCommandOptions :: [CmdOption]
shakeLintWatch :: [FilePath]
shakeLintIgnore :: [FilePath]
shakeLintInside :: [FilePath]
shakeLint :: Maybe Lint
shakeReport :: [FilePath]
shakeStaunch :: Bool
shakeVerbosity :: Verbosity
shakeVersion :: FilePath
shakeThreads :: Int
shakeFiles :: FilePath
shakeCreationCheck :: ShakeOptions -> Bool
shakeNeedDirectory :: ShakeOptions -> Bool
shakeChange :: ShakeOptions -> Change
..} <- Rules ShakeOptions
getShakeOptionsRules
    -- A rule from FileQ to (Maybe FileA). The result value is only useful for linting.
    forall key value.
(RuleResult key ~ value, ShakeValue key, BinaryEx key,
 Typeable value, NFData value, Show value, HasCallStack) =>
BuiltinLint key value
-> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRuleEx (ShakeOptions -> BuiltinLint FileQ FileR
ruleLint ShakeOptions
opts) (ShakeOptions -> BuiltinIdentity FileQ FileR
ruleIdentity ShakeOptions
opts) (ShakeOptions -> (FilePath -> Rebuild) -> BuiltinRun FileQ FileR
ruleRun ShakeOptions
opts forall a b. (a -> b) -> a -> b
$ ShakeOptions -> FilePath -> Rebuild
shakeRebuildApply ShakeOptions
opts)

ruleLint :: ShakeOptions -> BuiltinLint FileQ FileR
ruleLint :: ShakeOptions -> BuiltinLint FileQ FileR
ruleLint ShakeOptions
opts FileQ
k (FileR (Just FileA
v) Bool
True) = do
    Maybe FileA
now <- ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts FileQ
k
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case Maybe FileA
now of
        Maybe FileA
Nothing -> forall a. a -> Maybe a
Just FilePath
"<missing>"
        Just FileA
now | ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions
opts FileA
v FileA
now forall a. Eq a => a -> a -> Bool
== EqualCost
EqualCheap -> forall a. Maybe a
Nothing
                 | Bool
otherwise -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show FileA
now
ruleLint ShakeOptions
_ FileQ
_ FileR
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing

ruleIdentity :: ShakeOptions -> BuiltinIdentity FileQ FileR
ruleIdentity :: ShakeOptions -> BuiltinIdentity FileQ FileR
ruleIdentity ShakeOptions
opts | ShakeOptions -> Change
shakeChange ShakeOptions
opts forall a. Eq a => a -> a -> Bool
== Change
ChangeModtime = forall a. SomeException -> a
throwImpure SomeException
errorNoHash
ruleIdentity ShakeOptions
_ = \FileQ
k FileR
v -> case FileR -> Maybe FileA
answer FileR
v of
    Just (FileA ModTime
_ FileSize
size FileHash
hash) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
runBuilder forall a b. (a -> b) -> a -> b
$ forall a. Storable a => a -> Builder
putExStorable FileSize
size forall a. Semigroup a => a -> a -> a
<> forall a. Storable a => a -> Builder
putExStorable FileHash
hash
    Maybe FileA
Nothing -> forall a. Maybe a
Nothing

ruleRun :: ShakeOptions -> (FilePath -> Rebuild) -> BuiltinRun FileQ FileR
ruleRun :: ShakeOptions -> (FilePath -> Rebuild) -> BuiltinRun FileQ FileR
ruleRun opts :: ShakeOptions
opts@ShakeOptions{Bool
Int
FilePath
[FilePath]
[(FilePath, FilePath)]
[(Rebuild, FilePath)]
[CmdOption]
Maybe Seconds
Maybe FilePath
Maybe Lint
HashMap TypeRep Dynamic
Verbosity
Change
FilePath -> FilePath -> Bool -> IO ()
IO Progress -> IO ()
Verbosity -> FilePath -> IO ()
shakeExtra :: HashMap TypeRep Dynamic
shakeTrace :: FilePath -> FilePath -> Bool -> IO ()
shakeOutput :: Verbosity -> FilePath -> IO ()
shakeProgress :: IO Progress -> IO ()
shakeAllowRedefineRules :: Bool
shakeNeedDirectory :: Bool
shakeSymlink :: Bool
shakeCloud :: [FilePath]
shakeShare :: Maybe FilePath
shakeColor :: Bool
shakeVersionIgnore :: Bool
shakeLiveFiles :: [FilePath]
shakeCreationCheck :: Bool
shakeChange :: Change
shakeRunCommands :: Bool
shakeTimings :: Bool
shakeLineBuffering :: Bool
shakeStorageLog :: Bool
shakeAbbreviations :: [(FilePath, FilePath)]
shakeRebuild :: [(Rebuild, FilePath)]
shakeFlush :: Maybe Seconds
shakeCommandOptions :: [CmdOption]
shakeLintWatch :: [FilePath]
shakeLintIgnore :: [FilePath]
shakeLintInside :: [FilePath]
shakeLint :: Maybe Lint
shakeReport :: [FilePath]
shakeStaunch :: Bool
shakeVerbosity :: Verbosity
shakeVersion :: FilePath
shakeThreads :: Int
shakeFiles :: FilePath
shakeExtra :: ShakeOptions -> HashMap TypeRep Dynamic
shakeTrace :: ShakeOptions -> FilePath -> FilePath -> Bool -> IO ()
shakeOutput :: ShakeOptions -> Verbosity -> FilePath -> IO ()
shakeProgress :: ShakeOptions -> IO Progress -> IO ()
shakeAllowRedefineRules :: ShakeOptions -> Bool
shakeSymlink :: ShakeOptions -> Bool
shakeCloud :: ShakeOptions -> [FilePath]
shakeShare :: ShakeOptions -> Maybe FilePath
shakeColor :: ShakeOptions -> Bool
shakeVersionIgnore :: ShakeOptions -> Bool
shakeLiveFiles :: ShakeOptions -> [FilePath]
shakeRunCommands :: ShakeOptions -> Bool
shakeTimings :: ShakeOptions -> Bool
shakeLineBuffering :: ShakeOptions -> Bool
shakeStorageLog :: ShakeOptions -> Bool
shakeAbbreviations :: ShakeOptions -> [(FilePath, FilePath)]
shakeRebuild :: ShakeOptions -> [(Rebuild, FilePath)]
shakeFlush :: ShakeOptions -> Maybe Seconds
shakeCommandOptions :: ShakeOptions -> [CmdOption]
shakeLintWatch :: ShakeOptions -> [FilePath]
shakeLintIgnore :: ShakeOptions -> [FilePath]
shakeLintInside :: ShakeOptions -> [FilePath]
shakeLint :: ShakeOptions -> Maybe Lint
shakeReport :: ShakeOptions -> [FilePath]
shakeStaunch :: ShakeOptions -> Bool
shakeVerbosity :: ShakeOptions -> Verbosity
shakeVersion :: ShakeOptions -> FilePath
shakeThreads :: ShakeOptions -> Int
shakeFiles :: ShakeOptions -> FilePath
shakeCreationCheck :: ShakeOptions -> Bool
shakeNeedDirectory :: ShakeOptions -> Bool
shakeChange :: ShakeOptions -> Change
..} FilePath -> Rebuild
rebuildFlags o :: FileQ
o@(FileQ (FileName -> FilePath
fileNameToString -> FilePath
xStr)) oldBin :: Maybe ByteString
oldBin@(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. BinaryEx a => ByteString -> a
getEx -> Maybe Answer
old :: Maybe Answer) RunMode
mode = do
    -- for One, rebuild makes perfect sense
    -- for Forward, we expect the child will have already rebuilt - Rebuild just lets us deal with code changes
    -- for Phony, it doesn't make that much sense, but probably isn't harmful?
    let r :: Rebuild
r = FilePath -> Rebuild
rebuildFlags FilePath
xStr

    (Maybe Ver
ruleVer, [(Int, Mode)]
ruleAct, SomeException
ruleErr) <- forall key a b.
(ShakeValue key, Typeable a) =>
key
-> (a -> Maybe FilePath)
-> (a -> Maybe b)
-> Action (Maybe Ver, [(Int, b)], SomeException)
getUserRuleInternal FileQ
o (\(FileRule FilePath
s FilePath -> Maybe Mode
_) -> forall a. a -> Maybe a
Just FilePath
s) forall a b. (a -> b) -> a -> b
$ \(FileRule FilePath
_ FilePath -> Maybe Mode
f) -> FilePath -> Maybe Mode
f FilePath
xStr
    let verEq :: Ver -> Bool
verEq Ver
v = forall a. a -> Maybe a
Just Ver
v forall a. Eq a => a -> a -> Bool
== Maybe Ver
ruleVer Bool -> Bool -> Bool
|| case [(Int, Mode)]
ruleAct of [] -> Ver
v forall a. Eq a => a -> a -> Bool
== Int -> Ver
Ver Int
0; [(Int
v2,Mode
_)] -> Ver
v forall a. Eq a => a -> a -> Bool
== Int -> Ver
Ver Int
v2; [(Int, Mode)]
_ -> Bool
False
    let rebuild :: Action (RunResult FileR)
rebuild = do
            Verbosity -> FilePath -> Action ()
putWhen Verbosity
Verbose forall a b. (a -> b) -> a -> b
$ FilePath
"# " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FileQ
o
            case [(Int, Mode)]
ruleAct of
                [] -> Maybe (Int, Mode) -> Action (RunResult FileR)
rebuildWith forall a. Maybe a
Nothing
                [(Int, Mode)
x] -> Maybe (Int, Mode) -> Action (RunResult FileR)
rebuildWith forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (Int, Mode)
x
                [(Int, Mode)]
_ -> forall (m :: * -> *) a. MonadIO m => SomeException -> m a
throwM SomeException
ruleErr

    case Maybe Answer
old of
        Maybe Answer
_ | Rebuild
r forall a. Eq a => a -> a -> Bool
== Rebuild
RebuildNow -> Action (RunResult FileR)
rebuild
        Maybe Answer
_ | Rebuild
r forall a. Eq a => a -> a -> Bool
== Rebuild
RebuildLater -> case Maybe Answer
old of
            Just Answer
_ ->
                -- ignoring the currently stored value, which may trigger lint has changed
                -- so disable lint on this file
                RunResult FileR -> RunResult FileR
unLint forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RunChanged -> Action (RunResult FileR)
retOld RunChanged
ChangedNothing
            Maybe Answer
Nothing -> do
                -- i don't have a previous value, so assume this is a source node, and mark rebuild in future
                Maybe FileA
now <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts FileQ
o
                case Maybe FileA
now of
                    Maybe FileA
Nothing -> Action (RunResult FileR)
rebuild
                    Just FileA
now -> do Action ()
alwaysRerun; RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
ChangedStore forall a b. (a -> b) -> a -> b
$ Ver -> FileA -> Answer
AnswerDirect (Int -> Ver
Ver Int
0) FileA
now
        {-
        _ | r == RebuildNever -> do
            now <- liftIO $ fileStoredValue opts o
            case now of
                Nothing -> rebuild
                Just now -> do
                    let diff | Just (AnswerDirect old) <- old, fileEqualValue opts old now /= NotEqual = ChangedRecomputeSame
                                | otherwise = ChangedRecomputeDiff
                    retNew diff $ AnswerDirect now
        -}
        Just (AnswerDirect Ver
ver FileA
old) | RunMode
mode forall a. Eq a => a -> a -> Bool
== RunMode
RunDependenciesSame, Ver -> Bool
verEq Ver
ver -> do
            Maybe FileA
now <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts FileQ
o
            let noHash :: FileA -> Bool
noHash (FileA ModTime
_ FileSize
_ FileHash
x) = FileHash -> Bool
isNoFileHash FileHash
x
            case Maybe FileA
now of
                Maybe FileA
Nothing -> Action (RunResult FileR)
rebuild
                Just FileA
now -> case ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions
opts FileA
old FileA
now of
                    EqualCost
NotEqual ->
                        Action (RunResult FileR)
rebuild
                    -- if our last build used no file hashing, but this build should, then we must refresh the hash
                    EqualCost
EqualCheap | if FileA -> Bool
noHash FileA
old then Change
shakeChange forall a. Eq a => a -> a -> Bool
== Change
ChangeModtimeAndDigestInput Bool -> Bool -> Bool
|| FileA -> Bool
noHash FileA
now else Bool
True ->
                        RunChanged -> Action (RunResult FileR)
retOld RunChanged
ChangedNothing
                    EqualCost
_ ->
                        RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
ChangedStore forall a b. (a -> b) -> a -> b
$ Ver -> FileA -> Answer
AnswerDirect Ver
ver FileA
now
        Just (AnswerForward Ver
ver FileA
_) | Ver -> Bool
verEq Ver
ver, RunMode
mode forall a. Eq a => a -> a -> Bool
== RunMode
RunDependenciesSame -> RunChanged -> Action (RunResult FileR)
retOld RunChanged
ChangedNothing
        Maybe Answer
_ -> Action (RunResult FileR)
rebuild
    where
        -- no need to lint check forward files
        -- but more than that, it goes wrong if you do, see #427
        fileR :: Answer -> FileR
fileR (AnswerDirect Ver
_ FileA
x) = Maybe FileA -> Bool -> FileR
FileR (forall a. a -> Maybe a
Just FileA
x) Bool
True
        fileR (AnswerForward Ver
_ FileA
x) = Maybe FileA -> Bool -> FileR
FileR (forall a. a -> Maybe a
Just FileA
x) Bool
False
        fileR Answer
AnswerPhony = Maybe FileA -> Bool -> FileR
FileR forall a. Maybe a
Nothing Bool
False
        unLint :: RunResult FileR -> RunResult FileR
unLint (RunResult RunChanged
a ByteString
b FileR
c) = forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
a ByteString
b FileR
c{useLint :: Bool
useLint = Bool
False}

        retNew :: RunChanged -> Answer -> Action (RunResult FileR)
        retNew :: RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
c Answer
v = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
c (Builder -> ByteString
runBuilder forall a b. (a -> b) -> a -> b
$ forall a. BinaryEx a => a -> Builder
putEx Answer
v) forall a b. (a -> b) -> a -> b
$ Answer -> FileR
fileR Answer
v

        retOld :: RunChanged -> Action (RunResult FileR)
        retOld :: RunChanged -> Action (RunResult FileR)
retOld RunChanged
c = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
c (forall a. HasCallStack => Maybe a -> a
fromJust Maybe ByteString
oldBin) forall a b. (a -> b) -> a -> b
$ Answer -> FileR
fileR (forall a. HasCallStack => Maybe a -> a
fromJust Maybe Answer
old)

        -- actually run the rebuild
        rebuildWith :: Maybe (Int, Mode) -> Action (RunResult FileR)
rebuildWith Maybe (Int, Mode)
act = do
            let answer :: (FileA -> Answer) -> FileA -> Action (RunResult FileR)
answer FileA -> Answer
ctor FileA
new = do
                    let b :: RunChanged
b = case () of
                                ()
_ | Just Answer
old <- Maybe Answer
old
                                    , Just FileA
old <- Answer -> Maybe FileA
fromAnswer Answer
old
                                    , ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions
opts FileA
old FileA
new forall a. Eq a => a -> a -> Bool
/= EqualCost
NotEqual -> RunChanged
ChangedRecomputeSame
                                ()
_ -> RunChanged
ChangedRecomputeDiff
                    RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
b forall a b. (a -> b) -> a -> b
$ FileA -> Answer
ctor FileA
new
            case Maybe (Int, Mode)
act of
                Maybe (Int, Mode)
Nothing -> do
                    Maybe FileA
new <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA)
storedValueError ShakeOptions
opts Bool
True FilePath
"Error, file does not exist and no rule available:" FileQ
o
                    (FileA -> Answer) -> FileA -> Action (RunResult FileR)
answer (Ver -> FileA -> Answer
AnswerDirect forall a b. (a -> b) -> a -> b
$ Int -> Ver
Ver Int
0)  forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust Maybe FileA
new
                Just (Int
ver, ModeForward Action (Maybe FileA)
act) -> do
                    Maybe FileA
new <- Action (Maybe FileA)
act
                    case Maybe FileA
new of
                        Maybe FileA
Nothing -> do
                            -- Not 100% sure how you get here, but I think it involves RebuildLater and multi-file rules
                            Action ()
historyDisable
                            RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
ChangedRecomputeDiff Answer
AnswerPhony
                        Just FileA
new -> (FileA -> Answer) -> FileA -> Action (RunResult FileR)
answer (Ver -> FileA -> Answer
AnswerForward forall a b. (a -> b) -> a -> b
$ Int -> Ver
Ver Int
ver) FileA
new
                Just (Int
ver, ModeDirect Action ()
act) -> do
                    Maybe ByteString
cache <- Int -> Action (Maybe ByteString)
historyLoad Int
ver
                    case Maybe ByteString
cache of
                        Just ByteString
encodedHash -> do
                            Just (FileA ModTime
mod FileSize
size FileHash
_) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA)
storedValueError ShakeOptions
opts Bool
False FilePath
"Error, restored the rule but did not produce file:" FileQ
o
                            (FileA -> Answer) -> FileA -> Action (RunResult FileR)
answer (Ver -> FileA -> Answer
AnswerDirect forall a b. (a -> b) -> a -> b
$ Int -> Ver
Ver Int
ver) forall a b. (a -> b) -> a -> b
$ ModTime -> FileSize -> FileHash -> FileA
FileA ModTime
mod FileSize
size forall a b. (a -> b) -> a -> b
$ forall a. Storable a => ByteString -> a
getExStorable ByteString
encodedHash
                        Maybe ByteString
Nothing -> do
                            Action ()
act
                            Maybe FileA
new <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA)
storedValueError ShakeOptions
opts Bool
False FilePath
"Error, rule finished running but did not produce file:" FileQ
o
                            case Maybe FileA
new of
                                Maybe FileA
Nothing -> do
                                    -- rule ran, but didn't compute an answer, because shakeCreationCheck=False
                                    -- I think it should probably not return phony, but return a different valid-but-no-file
                                    -- but it's just too rare to bother
                                    Action ()
historyDisable
                                    RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
ChangedRecomputeDiff Answer
AnswerPhony
                                Just new :: FileA
new@(FileA ModTime
_ FileSize
_ FileHash
fileHash) -> do
                                    [FilePath] -> Action ()
producesUnchecked [FilePath
xStr]
                                    RunResult FileR
res <- (FileA -> Answer) -> FileA -> Action (RunResult FileR)
answer (Ver -> FileA -> Answer
AnswerDirect forall a b. (a -> b) -> a -> b
$ Int -> Ver
Ver Int
ver) FileA
new
                                    Int -> ByteString -> Action ()
historySave Int
ver forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
runBuilder forall a b. (a -> b) -> a -> b
$
                                        if FileHash -> Bool
isNoFileHash FileHash
fileHash then forall a. SomeException -> a
throwImpure SomeException
errorNoHash else forall a. Storable a => a -> Builder
putExStorable FileHash
fileHash
                                    forall (f :: * -> *) a. Applicative f => a -> f a
pure RunResult FileR
res
                Just (Int
_, ModePhony Action ()
act) -> do
                    -- See #523 and #524
                    -- Shake runs the dependencies first, but stops when one has changed.
                    -- We don't want to run the existing deps first if someone changes the build system,
                    -- so insert a fake dependency that cuts the process dead.
                    Action ()
alwaysRerun
                    Action ()
act
                    RunChanged -> Answer -> Action (RunResult FileR)
retNew RunChanged
ChangedRecomputeDiff Answer
AnswerPhony


apply_ :: Partial => (a -> FileName) -> [a] -> Action [FileR]
apply_ :: forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR]
apply_ a -> FileName
f = forall key value.
(HasCallStack, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
[key] -> Action [value]
apply forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (FileName -> FileQ
FileQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> FileName
f)


-- | Has a file changed. This function will only give the correct answer if called in the rule
--   producing the file, /before/ the rule has modified the file in question.
--   Best avoided, but sometimes necessary in conjunction with 'needHasChanged' to cause rebuilds
--   to happen if the result is deleted or modified.
resultHasChanged :: FilePath -> Action Bool
resultHasChanged :: FilePath -> Action Bool
resultHasChanged FilePath
file = do
    let filename :: FileQ
filename = FileName -> FileQ
FileQ forall a b. (a -> b) -> a -> b
$ FilePath -> FileName
fileNameFromString FilePath
file
    Maybe (Result (Either ByteString FileR))
res <- forall key value.
(RuleResult key ~ value, ShakeValue key, Typeable value) =>
key -> Action (Maybe (Result (Either ByteString value)))
getDatabaseValue FileQ
filename
    Maybe FileA
old<- forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case forall a. Result a -> a
result forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Result (Either ByteString FileR))
res of
        Maybe (Either ByteString FileR)
Nothing -> forall a. Maybe a
Nothing
        Just (Left ByteString
bs) -> Answer -> Maybe FileA
fromAnswer forall a b. (a -> b) -> a -> b
$ forall a. BinaryEx a => ByteString -> a
getEx ByteString
bs
        Just (Right FileR
v) -> FileR -> Maybe FileA
answer FileR
v
    case Maybe FileA
old of
        Maybe FileA
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
        Just FileA
old -> do
            ShakeOptions
opts <- Action ShakeOptions
getShakeOptions
            Maybe FileA
new <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts FileQ
filename
            forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case Maybe FileA
new of
                Maybe FileA
Nothing -> Bool
True
                Just FileA
new -> ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions
opts FileA
old FileA
new forall a. Eq a => a -> a -> Bool
== EqualCost
NotEqual


---------------------------------------------------------------------
-- OPTIONS ON TOP

-- | Internal method for adding forwarding actions
fileForward :: String -> (FilePath -> Maybe (Action (Maybe FileA))) -> Rules ()
fileForward :: FilePath -> (FilePath -> Maybe (Action (Maybe FileA))) -> Rules ()
fileForward FilePath
help FilePath -> Maybe (Action (Maybe FileA))
act = forall a. Typeable a => a -> Rules ()
addUserRule forall a b. (a -> b) -> a -> b
$ FilePath -> (FilePath -> Maybe Mode) -> FileRule
FileRule FilePath
help forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Action (Maybe FileA) -> Mode
ModeForward forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe (Action (Maybe FileA))
act


-- | Add a dependency on the file arguments, ensuring they are built before continuing.
--   The file arguments may be built in parallel, in any order. This function is particularly
--   necessary when calling 'Development.Shake.cmd' or 'Development.Shake.command'. As an example:
--
-- @
-- \"\/\/*.rot13\" '%>' \\out -> do
--     let src = 'Development.Shake.FilePath.dropExtension' out
--     'need' [src]
--     'Development.Shake.cmd' \"rot13\" [src] \"-o\" [out]
-- @
--
--   Usually @need [foo,bar]@ is preferable to @need [foo] >> need [bar]@ as the former allows greater
--   parallelism, while the latter requires @foo@ to finish building before starting to build @bar@.
--
--   This function should not be called with wildcards (e.g. @*.txt@ - use 'getDirectoryFiles' to expand them),
--   environment variables (e.g. @$HOME@ - use 'getEnv' to expand them) or directories (directories cannot be
--   tracked directly - track files within the directory instead).
need :: Partial => [FilePath] -> Action ()
need :: HasCallStack => [FilePath] -> Action ()
need = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR]
apply_ FilePath -> FileName
fileNameFromString


-- | Like 'need' but returns a list of rebuilt dependencies since the calling rule last built successfully.
--
--   The following example writes a list of changed dependencies to a file as its action.
--
-- @
-- \"target\" '%>' \\out -> do
--       let sourceList = [\"source1\", \"source2\"]
--       rebuildList <- 'needHasChanged' sourceList
--       'Development.Shake.writeFileLines' out rebuildList
-- @
--
--   This function can be used to alter the action depending on which dependency needed
--   to be rebuild.
--
--   Note that a rule can be run even if no dependency has changed, for example
--   because of 'shakeRebuild' or because the target has changed or been deleted.
--   To detect the latter case you may wish to use 'resultHasChanged'.
needHasChanged :: Partial => [FilePath] -> Action [FilePath]
needHasChanged :: HasCallStack => [FilePath] -> Action [FilePath]
needHasChanged [FilePath]
paths = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ do
    forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR]
apply_ FilePath -> FileName
fileNameFromString [FilePath]
paths
    Maybe Key
self <- Action (Maybe Key)
getCurrentKey
    Maybe (Result (Either ByteString Value))
selfVal <- case Maybe Key
self of
        Maybe Key
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
        Just Key
self -> Key -> Action (Maybe (Result (Either ByteString Value)))
getDatabaseValueGeneric Key
self
    case Maybe (Result (Either ByteString Value))
selfVal of
        Maybe (Result (Either ByteString Value))
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [FilePath]
paths -- never build before or not a key, so everything has changed
        Just Result (Either ByteString Value)
selfVal -> forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM [FilePath]
paths forall a b. (a -> b) -> a -> b
$ \FilePath
path -> do
            Maybe (Result (Either ByteString FileR))
pathVal <- forall key value.
(RuleResult key ~ value, ShakeValue key, Typeable value) =>
key -> Action (Maybe (Result (Either ByteString value)))
getDatabaseValue (FileName -> FileQ
FileQ forall a b. (a -> b) -> a -> b
$ FilePath -> FileName
fileNameFromString FilePath
path)
            forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case Maybe (Result (Either ByteString FileR))
pathVal of
                Just Result (Either ByteString FileR)
pathVal | forall a. Result a -> Step
changed Result (Either ByteString FileR)
pathVal forall a. Ord a => a -> a -> Bool
> forall a. Result a -> Step
built Result (Either ByteString Value)
selfVal -> Bool
True
                Maybe (Result (Either ByteString FileR))
_ -> Bool
False


needBS :: Partial => [BS.ByteString] -> Action ()
needBS :: HasCallStack => [ByteString] -> Action ()
needBS = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR]
apply_ ByteString -> FileName
fileNameFromByteString

-- | Like 'need', but if 'shakeLint' is set, check that the file does not rebuild.
--   Used for adding dependencies on files that have already been used in this rule.
needed :: Partial => [FilePath] -> Action ()
needed :: HasCallStack => [FilePath] -> Action ()
needed [FilePath]
xs = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ do
    ShakeOptions
opts <- Action ShakeOptions
getShakeOptions
    if forall a. Maybe a -> Bool
isNothing forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Maybe Lint
shakeLint ShakeOptions
opts then HasCallStack => [FilePath] -> Action ()
need [FilePath]
xs else HasCallStack => [FileName] -> Action ()
neededCheck forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FileName
fileNameFromString [FilePath]
xs


neededBS :: Partial => [BS.ByteString] -> Action ()
neededBS :: HasCallStack => [ByteString] -> Action ()
neededBS [ByteString]
xs = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ do
    ShakeOptions
opts <- Action ShakeOptions
getShakeOptions
    if forall a. Maybe a -> Bool
isNothing forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Maybe Lint
shakeLint ShakeOptions
opts then HasCallStack => [ByteString] -> Action ()
needBS [ByteString]
xs else HasCallStack => [FileName] -> Action ()
neededCheck forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ByteString -> FileName
fileNameFromByteString [ByteString]
xs


neededCheck :: Partial => [FileName] -> Action ()
neededCheck :: HasCallStack => [FileName] -> Action ()
neededCheck [FileName]
xs = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ do
    ShakeOptions
opts <- Action ShakeOptions
getShakeOptions
    [Maybe FileA]
pre <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (ShakeOptions -> FileQ -> IO (Maybe FileA)
fileStoredValue ShakeOptions
opts forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileName -> FileQ
FileQ) [FileName]
xs
    [FileR]
post <- forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR]
apply_ forall a. a -> a
id [FileName]
xs
    let bad :: [(FileName, FilePath)]
bad = [ (FileName
x, if forall a. Maybe a -> Bool
isJust Maybe FileA
a then FilePath
"File change" else FilePath
"File created")
              | (FileName
x, Maybe FileA
a, FileR (Just FileA
b) Bool
_) <- forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [FileName]
xs [Maybe FileA]
pre [FileR]
post, forall b a. b -> (a -> b) -> Maybe a -> b
maybe EqualCost
NotEqual (\FileA
a -> ShakeOptions -> FileA -> FileA -> EqualCost
fileEqualValue ShakeOptions
opts FileA
a FileA
b) Maybe FileA
a forall a. Eq a => a -> a -> Bool
== EqualCost
NotEqual]
    case [(FileName, FilePath)]
bad of
        [] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        (FileName
file,FilePath
msg):[(FileName, FilePath)]
_ -> forall (m :: * -> *) a. MonadIO m => SomeException -> m a
throwM forall a b. (a -> b) -> a -> b
$ FilePath
-> [(FilePath, Maybe FilePath)] -> FilePath -> SomeException
errorStructured
            FilePath
"Lint checking error - 'needed' file required rebuilding"
            [(FilePath
"File", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ FileName -> FilePath
fileNameToString FileName
file)
            ,(FilePath
"Error",forall a. a -> Maybe a
Just FilePath
msg)]
            FilePath
""


-- Either trackRead or trackWrite
track :: ([FileQ] -> Action ()) -> [FilePath] -> Action ()
track :: ([FileQ] -> Action ()) -> [FilePath] -> Action ()
track [FileQ] -> Action ()
tracker [FilePath]
xs = do
    ShakeOptions{[FilePath]
shakeLintIgnore :: [FilePath]
shakeLintIgnore :: ShakeOptions -> [FilePath]
shakeLintIgnore} <- Action ShakeOptions
getShakeOptions
    let ignore :: FilePath -> Bool
ignore = [FilePath] -> FilePath -> Bool
(?==*) [FilePath]
shakeLintIgnore
    let ys :: [FilePath]
ys = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Bool
ignore) [FilePath]
xs
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([FilePath]
ys forall a. Eq a => a -> a -> Bool
/= []) forall a b. (a -> b) -> a -> b
$
        [FileQ] -> Action ()
tracker forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (FileName -> FileQ
FileQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FileName
fileNameFromString) [FilePath]
ys


-- | Track that a file was read by the action preceding it. If 'shakeLint' is activated
--   then these files must be dependencies of this rule. Calls to 'trackRead' are
--   automatically inserted in 'LintFSATrace' mode.
trackRead :: [FilePath] -> Action ()
trackRead :: [FilePath] -> Action ()
trackRead = ([FileQ] -> Action ()) -> [FilePath] -> Action ()
track forall key. ShakeValue key => [key] -> Action ()
lintTrackRead


-- | Track that a file was written by the action preceding it. If 'shakeLint' is activated
--   then these files must either be the target of this rule, or never referred to by the build system.
--   Calls to 'trackWrite' are automatically inserted in 'LintFSATrace' mode.
trackWrite :: [FilePath] -> Action ()
trackWrite :: [FilePath] -> Action ()
trackWrite = ([FileQ] -> Action ()) -> [FilePath] -> Action ()
track forall key. ShakeValue key => [key] -> Action ()
lintTrackWrite

-- | Allow accessing a file in this rule, ignoring any subsequent 'trackRead' \/ 'trackWrite' calls matching
--   the pattern.
trackAllow :: [FilePattern] -> Action ()
trackAllow :: [FilePath] -> Action ()
trackAllow [FilePath]
ps = do
    let ignore :: FilePath -> Bool
ignore = [FilePath] -> FilePath -> Bool
(?==*) [FilePath]
ps
    forall key. ShakeValue key => (key -> Bool) -> Action ()
lintTrackAllow forall a b. (a -> b) -> a -> b
$ \(FileQ FileName
x) -> FilePath -> Bool
ignore forall a b. (a -> b) -> a -> b
$ FileName -> FilePath
fileNameToString FileName
x


-- | This rule builds the following files, in addition to any defined by its target.
--   At the end of the rule these files must have been written.
--   These files must /not/ be tracked as part of the build system - two rules cannot produce
--   the same file and you cannot 'need' the files it produces.
produces :: [FilePath] -> Action ()
produces :: [FilePath] -> Action ()
produces [FilePath]
xs = do
    [FilePath] -> Action ()
producesChecked [FilePath]
xs
    [FilePath] -> Action ()
trackWrite [FilePath]
xs


-- | Require that the argument files are built by the rules, used to specify the target.
--
-- @
-- main = 'Development.Shake.shake' 'shakeOptions' $ do
--    'want' [\"Main.exe\"]
--    ...
-- @
--
--   This program will build @Main.exe@, given sufficient rules. All arguments to all 'want' calls
--   may be built in parallel, in any order.
--
--   This function is defined in terms of 'action' and 'need', use 'action' if you need more complex
--   targets than 'want' allows.
want :: Partial => [FilePath] -> Rules ()
want :: HasCallStack => [FilePath] -> Rules ()
want [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
want [FilePath]
xs = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Action a -> Rules ()
action forall a b. (a -> b) -> a -> b
$ HasCallStack => [FilePath] -> Action ()
need [FilePath]
xs


root :: String -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root :: FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root FilePath
help FilePath -> Bool
test FilePath -> Action ()
act = forall a. Typeable a => a -> Rules ()
addUserRule forall a b. (a -> b) -> a -> b
$ FilePath -> (FilePath -> Maybe Mode) -> FileRule
FileRule FilePath
help forall a b. (a -> b) -> a -> b
$ \FilePath
x -> if Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ FilePath -> Bool
test FilePath
x then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Action () -> Mode
ModeDirect forall a b. (a -> b) -> a -> b
$ do
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
createDirectoryRecursive forall a b. (a -> b) -> a -> b
$ ShowS
takeDirectory FilePath
x
    FilePath -> Action ()
act FilePath
x


-- | Declare a Make-style phony action.  A phony target does not name
--   a file (despite living in the same namespace as file rules);
--   rather, it names some action to be executed when explicitly
--   requested.  You can demand 'phony' rules using 'want'. (And 'need',
--   although that's not recommended.)
--
--   Phony actions are intended to define recipes that can be executed
--   by the user. If you 'need' a phony action in a rule then every
--   execution where that rule is required will rerun both the rule and
--   the phony action.  However, note that phony actions are never
--   executed more than once in a single build run.
--
--   In make, the @.PHONY@ attribute on non-file-producing rules has a
--   similar effect.  However, while in make it is acceptable to omit
--   the @.PHONY@ attribute as long as you don't create the file in
--   question, a Shake rule which behaves this way will fail lint.
--   For file-producing rules which should be
--   rerun every execution of Shake, see 'Development.Shake.alwaysRerun'.
phony :: Located => String -> Action () -> Rules ()
phony :: HasCallStack => FilePath -> Action () -> Rules ()
phony oname :: FilePath
oname@(ShowS
toStandard -> FilePath
name) Action ()
act = do
    FilePath -> Rules ()
addTarget FilePath
oname
    FilePath -> (FilePath -> Maybe (Action ())) -> Rules ()
addPhony (FilePath
"phony " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
oname forall a. [a] -> [a] -> [a]
++ FilePath
" at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop) forall a b. (a -> b) -> a -> b
$ \FilePath
s -> if FilePath
s forall a. Eq a => a -> a -> Bool
== FilePath
name then forall a. a -> Maybe a
Just Action ()
act else forall a. Maybe a
Nothing

-- | A predicate version of 'phony', return 'Just' with the 'Action' for the matching rules.
phonys :: Located => (String -> Maybe (Action ())) -> Rules ()
phonys :: HasCallStack => (FilePath -> Maybe (Action ())) -> Rules ()
phonys = FilePath -> (FilePath -> Maybe (Action ())) -> Rules ()
addPhony (FilePath
"phonys at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop)

-- | Infix operator alias for 'phony', for sake of consistency with normal
--   rules.
(~>) :: Located => String -> Action () -> Rules ()
~> :: HasCallStack => FilePath -> Action () -> Rules ()
(~>) oname :: FilePath
oname@(ShowS
toStandard -> FilePath
name) Action ()
act = do
    FilePath -> Rules ()
addTarget FilePath
oname
    FilePath -> (FilePath -> Maybe (Action ())) -> Rules ()
addPhony (forall a. Show a => a -> FilePath
show FilePath
oname forall a. [a] -> [a] -> [a]
++ FilePath
" ~> at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop) forall a b. (a -> b) -> a -> b
$ \FilePath
s -> if FilePath
s forall a. Eq a => a -> a -> Bool
== FilePath
name then forall a. a -> Maybe a
Just Action ()
act else forall a. Maybe a
Nothing

addPhony :: String -> (String -> Maybe (Action ())) -> Rules ()
addPhony :: FilePath -> (FilePath -> Maybe (Action ())) -> Rules ()
addPhony FilePath
help FilePath -> Maybe (Action ())
act = forall a. Typeable a => a -> Rules ()
addUserRule forall a b. (a -> b) -> a -> b
$ FilePath -> (FilePath -> Maybe Mode) -> FileRule
FileRule FilePath
help forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Action () -> Mode
ModePhony forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe (Action ())
act


-- | Define a rule to build files. If the first argument returns 'True' for a given file,
--   the second argument will be used to build it. Usually '%>' is sufficient, but '?>' gives
--   additional power. For any file used by the build system, only one rule should return 'True'.
--   This function will create the directory for the result file, if necessary.
--
-- @
-- (all isUpper . 'Development.Shake.FilePath.takeBaseName') '?>' \\out -> do
--     let src = 'Development.Shake.FilePath.replaceBaseName' out $ map toLower $ takeBaseName out
--     'Development.Shake.writeFile'' out . map toUpper =<< 'Development.Shake.readFile'' src
-- @
--
--   If the 'Action' completes successfully the file is considered up-to-date, even if the file
--   has not changed.
(?>) :: Located => (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
?> :: HasCallStack =>
(FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
(?>) FilePath -> Bool
test FilePath -> Action ()
act = forall a. Seconds -> Rules a -> Rules a
priority Seconds
0.5 forall a b. (a -> b) -> a -> b
$ FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root (FilePath
"?> at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop) FilePath -> Bool
test FilePath -> Action ()
act


-- | Define a set of patterns, and if any of them match, run the associated rule. Defined in terms of '%>'.
--   Think of it as the OR (@||@) equivalent of '%>'.
(|%>) :: Located => [FilePattern] -> (FilePath -> Action ()) -> Rules ()
|%> :: HasCallStack => [FilePath] -> (FilePath -> Action ()) -> Rules ()
(|%>) [FilePath]
pats FilePath -> Action ()
act = do
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ FilePath -> Rules ()
addTarget [FilePath]
pats
    let ([FilePath]
simp,[FilePath]
other) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition FilePath -> Bool
simple [FilePath]
pats
    case forall a b. (a -> b) -> [a] -> [b]
map ShowS
toStandard [FilePath]
simp of
        [] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        [FilePath
p] -> FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root FilePath
help (\FilePath
x -> ShowS
toStandard FilePath
x forall a. Eq a => a -> a -> Bool
== FilePath
p) FilePath -> Action ()
act
        [FilePath]
ps -> let set :: HashSet FilePath
set = forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList [FilePath]
ps in FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root FilePath
help (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
Set.member HashSet FilePath
set forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
toStandard) FilePath -> Action ()
act
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
other) forall a b. (a -> b) -> a -> b
$
        let ps :: [FilePath -> Bool]
ps = forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath -> Bool
(?==) [FilePath]
other in forall a. Seconds -> Rules a -> Rules a
priority Seconds
0.5 forall a b. (a -> b) -> a -> b
$ FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root FilePath
help (\FilePath
x -> forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a b. (a -> b) -> a -> b
$ FilePath
x) [FilePath -> Bool]
ps) FilePath -> Action ()
act
    where help :: FilePath
help = forall a. Show a => a -> FilePath
show [FilePath]
pats forall a. [a] -> [a] -> [a]
++ FilePath
" |%> at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop

-- | Define a rule that matches a 'FilePattern', see '?==' for the pattern rules.
--   Patterns with no wildcards have higher priority than those with wildcards, and no file
--   required by the system may be matched by more than one pattern at the same priority
--   (see 'priority' and 'alternatives' to modify this behaviour).
--   This function will create the directory for the result file, if necessary.
--
-- @
-- \"*.asm.o\" '%>' \\out -> do
--     let src = 'Development.Shake.FilePath.dropExtension' out
--     'need' [src]
--     'Development.Shake.cmd' \"as\" [src] \"-o\" [out]
-- @
--
--   To define a build system for multiple compiled languages, we recommend using @.asm.o@,
--   @.cpp.o@, @.hs.o@, to indicate which language produces an object file.
--   I.e., the file @foo.cpp@ produces object file @foo.cpp.o@.
--
--   Note that matching is case-sensitive, even on Windows.
--
--   If the 'Action' completes successfully the file is considered up-to-date, even if the file
--   has not changed.
(%>) :: Located => FilePattern -> (FilePath -> Action ()) -> Rules ()
%> :: HasCallStack => FilePath -> (FilePath -> Action ()) -> Rules ()
(%>) FilePath
test FilePath -> Action ()
act = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$
    (if FilePath -> Bool
simple FilePath
test then forall a. a -> a
id else forall a. Seconds -> Rules a -> Rules a
priority Seconds
0.5) forall a b. (a -> b) -> a -> b
$ do
        FilePath -> Rules ()
addTarget FilePath
test
        FilePath
-> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules ()
root (forall a. Show a => a -> FilePath
show FilePath
test forall a. [a] -> [a] -> [a]
++ FilePath
" %> at " forall a. [a] -> [a] -> [a]
++ HasCallStack => FilePath
callStackTop) (FilePath
test FilePath -> FilePath -> Bool
?==) FilePath -> Action ()
act