{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, ScopedTypeVariables, NamedFieldPuns #-}{-# LANGUAGE ViewPatterns, RecordWildCards, FlexibleInstances, TypeFamilies, ConstraintKinds #-}moduleDevelopment.Shake.Internal.Rules.File(need ,needHasChanged ,needBS ,needed ,neededBS ,want ,trackRead ,trackWrite ,trackAllow ,produces ,defaultRuleFile ,(%>) ,(|%>) ,(?>) ,phony ,(~>) ,phonys ,resultHasChanged ,-- * Internal onlyFileQ (..),FileA (..),fileStoredValue ,fileEqualValue ,EqualCost (..),fileForward )whereimportControl.Monad.ExtraimportControl.Monad.IO.ClassimportData.TypeableimportData.ListimportData.MaybeimportqualifiedData.ByteString.Char8asBSimportqualifiedData.HashSetasSetimportForeign.StorableimportData.WordimportData.MonoidimportGeneral.Binary importGeneral.Extra importDevelopment.Shake.Internal.Core.Types importDevelopment.Shake.Internal.Core.Rules importDevelopment.Shake.Internal.Core.Build importDevelopment.Shake.Internal.Core.Action importDevelopment.Shake.Internal.FileName importDevelopment.Shake.Internal.Rules.Rerun importDevelopment.Shake.Classes importDevelopment.Shake.FilePath (toStandard )importDevelopment.Shake.Internal.FilePattern importDevelopment.Shake.Internal.FileInfo importDevelopment.Shake.Internal.Options importDevelopment.Shake.Internal.Errors importSystem.FilePath(takeDirectory)-- important that this is the system local filepath, or wrong slashes go wrongimportSystem.IO.Unsafe(unsafeInterleaveIO)importPreludeinfix1%> ,?> ,|%> ,~> ----------------------------------------------------------------------- TYPEStypeinstanceRuleResult FileQ =FileR -- | The unique key we use to index File rules, to avoid name clashes.newtypeFileQ =FileQ {FileQ -> FileName fromFileQ ::FileName }deriving(Typeable,FileQ -> FileQ -> Bool (FileQ -> FileQ -> Bool) -> (FileQ -> FileQ -> Bool) -> Eq FileQ forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: FileQ -> FileQ -> Bool == :: FileQ -> FileQ -> Bool $c/= :: FileQ -> FileQ -> Bool /= :: FileQ -> FileQ -> Bool Eq,Eq FileQ Eq FileQ => (Int -> FileQ -> Int) -> (FileQ -> Int) -> Hashable FileQ Int -> FileQ -> Int FileQ -> Int forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a $chashWithSalt :: Int -> FileQ -> Int hashWithSalt :: Int -> FileQ -> Int $chash :: FileQ -> Int hash :: FileQ -> Int Hashable,Get FileQ [FileQ] -> Put FileQ -> Put (FileQ -> Put) -> Get FileQ -> ([FileQ] -> Put) -> Binary FileQ forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t $cput :: FileQ -> Put put :: FileQ -> Put $cget :: Get FileQ get :: Get FileQ $cputList :: [FileQ] -> Put putList :: [FileQ] -> Put Binary,ByteString -> FileQ FileQ -> Builder (FileQ -> Builder) -> (ByteString -> FileQ) -> BinaryEx FileQ forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a $cputEx :: FileQ -> Builder putEx :: FileQ -> Builder $cgetEx :: ByteString -> FileQ getEx :: ByteString -> FileQ BinaryEx ,FileQ -> () (FileQ -> ()) -> NFData FileQ forall a. (a -> ()) -> NFData a $crnf :: FileQ -> () rnf :: FileQ -> () NFData)-- | Raw information about a file.dataFileA =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 builddataFileR =FileR {FileR -> Maybe FileA answer ::!(MaybeFileA )-- ^ 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.dataMode =ModePhony (Action ())-- ^ An action with no file value|ModeDirect (Action ())-- ^ An action that produces this file|ModeForward (Action (MaybeFileA ))-- ^ An action that looks up a file someone else produced-- | The results of the various 'Mode' rules.dataAnswer =AnswerPhony |AnswerDirect Ver FileA |AnswerForward Ver FileA -- | The file rules we use, first is the name (as pretty as you can get).dataFileRule =FileRule String(FilePath->MaybeMode )derivingTypeable----------------------------------------------------------------------- INSTANCESinstanceShowFileQ whereshow :: FileQ -> FilePath show (FileQ FileName x )=FileName -> FilePath fileNameToString FileName x instanceBinaryEx [FileQ ]whereputEx :: [FileQ] -> Builder putEx =[FileName] -> Builder forall a. BinaryEx a => a -> Builder putEx ([FileName] -> Builder) -> ([FileQ] -> [FileName]) -> [FileQ] -> Builder forall b c a. (b -> c) -> (a -> b) -> a -> c .(FileQ -> FileName) -> [FileQ] -> [FileName] forall a b. (a -> b) -> [a] -> [b] mapFileQ -> FileName fromFileQ getEx :: ByteString -> [FileQ] getEx =(FileName -> FileQ) -> [FileName] -> [FileQ] forall a b. (a -> b) -> [a] -> [b] mapFileName -> FileQ FileQ ([FileName] -> [FileQ]) -> (ByteString -> [FileName]) -> ByteString -> [FileQ] forall b c a. (b -> c) -> (a -> b) -> a -> c .ByteString -> [FileName] forall a. BinaryEx a => ByteString -> a getEx instanceNFDataFileA wherernf :: FileA -> () rnf (FileA ModTime a FileSize b FileHash c )=ModTime -> () forall a. NFData a => a -> () rnfModTime a () -> () -> () forall a b. a -> b -> b `seq`FileSize -> () forall a. NFData a => a -> () rnfFileSize b () -> () -> () forall a b. a -> b -> b `seq`FileHash -> () forall a. NFData a => a -> () rnfFileHash c instanceNFDataFileR wherernf :: FileR -> () rnf(FileR Maybe FileA a Bool b )=Maybe FileA -> () forall a. NFData a => a -> () rnfMaybe FileA a () -> () -> () forall a b. a -> b -> b `seq`Bool -> () forall a. NFData a => a -> () rnfBool b instanceShowFileA whereshow :: FileA -> FilePath show(FileA ModTime m FileSize s FileHash h )=FilePath "File {mod="FilePath -> ShowS forall a. [a] -> [a] -> [a] ++ModTime -> FilePath forall a. Show a => a -> FilePath showModTime m FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath ",size="FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FileSize -> FilePath forall a. Show a => a -> FilePath showFileSize s FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath ",digest="FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FileHash -> FilePath forall a. Show a => a -> FilePath showFileHash h FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath "}"instanceShowFileR whereshow :: FileR -> FilePath showFileR {Bool Maybe FileA answer :: FileR -> Maybe FileA useLint :: FileR -> Bool answer :: Maybe FileA useLint :: Bool .. }=Maybe FileA -> FilePath forall a. Show a => a -> FilePath showMaybe FileA answer instanceStorableFileA wheresizeOf :: FileA -> Int sizeOf FileA _=Int 4Int -> Int -> Int forall a. Num a => a -> a -> a *Int 3-- 4 Word32'salignment :: FileA -> Int alignment FileA _=ModTime -> Int forall a. Storable a => a -> Int alignment(ModTime 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 (ModTime -> FileSize -> FileHash -> FileA) -> IO ModTime -> IO (FileSize -> FileHash -> FileA) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>Ptr b -> Int -> IO ModTime forall b. Ptr b -> Int -> IO ModTime forall a b. Storable a => Ptr b -> Int -> IO a peekByteOffPtr b p Int i IO (FileSize -> FileHash -> FileA) -> IO FileSize -> IO (FileHash -> FileA) forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*>Ptr b -> Int -> IO FileSize forall b. Ptr b -> Int -> IO FileSize forall a b. Storable a => Ptr b -> Int -> IO a peekByteOffPtr b p (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 4)IO (FileHash -> FileA) -> IO FileHash -> IO FileA forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*>Ptr b -> Int -> IO FileHash forall b. Ptr b -> Int -> IO FileHash forall a b. Storable a => Ptr b -> Int -> IO a peekByteOffPtr b p (Int i Int -> Int -> Int forall 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 )=Ptr b -> Int -> ModTime -> IO () forall b. Ptr b -> Int -> ModTime -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOffPtr b p Int i ModTime a IO () -> IO () -> IO () forall a b. IO a -> IO b -> IO b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>Ptr b -> Int -> FileSize -> IO () forall b. Ptr b -> Int -> FileSize -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOffPtr b p (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 4)FileSize b IO () -> IO () -> IO () forall a b. IO a -> IO b -> IO b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>Ptr b -> Int -> FileHash -> IO () forall b. Ptr b -> Int -> FileHash -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOffPtr b p (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 8)FileHash c instanceBinaryEx FileA whereputEx :: FileA -> Builder putEx =FileA -> Builder forall a. Storable a => a -> Builder putExStorable getEx :: ByteString -> FileA getEx =ByteString -> FileA forall a. Storable a => ByteString -> a getExStorable instanceBinaryEx [FileA ]whereputEx :: [FileA] -> Builder putEx =[FileA] -> Builder forall a. Storable a => [a] -> Builder putExStorableList getEx :: ByteString -> [FileA] getEx =ByteString -> [FileA] forall a. Storable a => ByteString -> [a] getExStorableList fromAnswer ::Answer ->MaybeFileA fromAnswer :: Answer -> Maybe FileA fromAnswer Answer AnswerPhony =Maybe FileA forall a. Maybe a NothingfromAnswer (AnswerDirect Ver _FileA x )=FileA -> Maybe FileA forall a. a -> Maybe a JustFileA x fromAnswer (AnswerForward Ver _FileA x )=FileA -> Maybe FileA forall a. a -> Maybe a JustFileA x instanceBinaryEx Answer whereputEx :: Answer -> Builder putEx Answer AnswerPhony =Builder forall a. Monoid a => a memptyputEx (AnswerDirect Ver ver FileA x )=Ver -> Builder forall a. Storable a => a -> Builder putExStorable Ver ver Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <>FileA -> Builder forall a. BinaryEx a => a -> Builder putEx FileA x putEx (AnswerForward Ver ver FileA x )=Word8 -> Builder forall a. BinaryEx a => a -> Builder putEx (Word8 0::Word8)Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <>Ver -> Builder forall a. Storable a => a -> Builder putExStorable Ver ver Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <>FileA -> Builder forall a. BinaryEx a => a -> Builder putEx FileA x getEx :: ByteString -> Answer getEx ByteString x =caseByteString -> Int BS.lengthByteString x ofInt 0->Answer AnswerPhony Int i ->ifInt i Int -> Int -> Bool forall a. Eq a => a -> a -> Bool ==Int sz then(Ver -> FileA -> Answer) -> ByteString -> Answer forall {t} {a} {b}. (Storable t, BinaryEx a) => (t -> a -> b) -> ByteString -> b f Ver -> FileA -> Answer AnswerDirect ByteString x else(Ver -> FileA -> Answer) -> ByteString -> Answer forall {t} {a} {b}. (Storable t, BinaryEx a) => (t -> a -> b) -> ByteString -> b f Ver -> FileA -> Answer AnswerForward (ByteString -> Answer) -> ByteString -> Answer forall a b. (a -> b) -> a -> b $HasCallStack => ByteString -> ByteString ByteString -> ByteString BS.tailByteString x wheresz :: Int sz =Ver -> Int forall a. Storable a => a -> Int sizeOf(Ver forall a. HasCallStack => a undefined::Ver )Int -> Int -> Int forall a. Num a => a -> a -> a +FileA -> Int forall a. Storable a => a -> Int sizeOf(FileA forall a. HasCallStack => a undefined::FileA )f :: (t -> a -> b) -> ByteString -> b f t -> a -> b ctor ByteString x =let(t a ,ByteString b )=ByteString -> (t, ByteString) forall a. Storable a => ByteString -> (a, ByteString) binarySplit ByteString x int -> a -> b ctor t a (a -> b) -> a -> b forall a b. (a -> b) -> a -> b $ByteString -> a forall a. BinaryEx a => ByteString -> a getEx ByteString b ----------------------------------------------------------------------- FILE CHECK QUERIES-- | An equality check and a cost.dataEqualCost =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 (EqualCost -> EqualCost -> Bool) -> (EqualCost -> EqualCost -> Bool) -> Eq EqualCost forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: EqualCost -> EqualCost -> Bool == :: EqualCost -> EqualCost -> Bool $c/= :: EqualCost -> EqualCost -> Bool /= :: EqualCost -> EqualCost -> Bool Eq,Eq EqualCost Eq EqualCost => (EqualCost -> EqualCost -> Ordering) -> (EqualCost -> EqualCost -> Bool) -> (EqualCost -> EqualCost -> Bool) -> (EqualCost -> EqualCost -> Bool) -> (EqualCost -> EqualCost -> Bool) -> (EqualCost -> EqualCost -> EqualCost) -> (EqualCost -> EqualCost -> EqualCost) -> Ord 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 $ccompare :: EqualCost -> EqualCost -> Ordering compare :: EqualCost -> EqualCost -> Ordering $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 >= :: EqualCost -> EqualCost -> Bool $cmax :: EqualCost -> EqualCost -> EqualCost max :: EqualCost -> EqualCost -> EqualCost $cmin :: EqualCost -> EqualCost -> EqualCost min :: EqualCost -> EqualCost -> EqualCost Ord,Int -> EqualCost -> ShowS [EqualCost] -> ShowS EqualCost -> FilePath (Int -> EqualCost -> ShowS) -> (EqualCost -> FilePath) -> ([EqualCost] -> ShowS) -> Show EqualCost forall a. (Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> EqualCost -> ShowS showsPrec :: Int -> EqualCost -> ShowS $cshow :: EqualCost -> FilePath show :: EqualCost -> FilePath $cshowList :: [EqualCost] -> ShowS showList :: [EqualCost] -> ShowS Show,ReadPrec [EqualCost] ReadPrec EqualCost Int -> ReadS EqualCost ReadS [EqualCost] (Int -> ReadS EqualCost) -> ReadS [EqualCost] -> ReadPrec EqualCost -> ReadPrec [EqualCost] -> Read EqualCost forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a $creadsPrec :: Int -> ReadS EqualCost readsPrec :: Int -> ReadS EqualCost $creadList :: ReadS [EqualCost] readList :: ReadS [EqualCost] $creadPrec :: ReadPrec EqualCost readPrec :: ReadPrec EqualCost $creadListPrec :: ReadPrec [EqualCost] readListPrec :: ReadPrec [EqualCost] Read,Typeable,Int -> EqualCost EqualCost -> Int EqualCost -> [EqualCost] EqualCost -> EqualCost EqualCost -> EqualCost -> [EqualCost] EqualCost -> EqualCost -> EqualCost -> [EqualCost] (EqualCost -> EqualCost) -> (EqualCost -> EqualCost) -> (Int -> EqualCost) -> (EqualCost -> Int) -> (EqualCost -> [EqualCost]) -> (EqualCost -> EqualCost -> [EqualCost]) -> (EqualCost -> EqualCost -> [EqualCost]) -> (EqualCost -> EqualCost -> EqualCost -> [EqualCost]) -> Enum 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 $csucc :: EqualCost -> EqualCost succ :: EqualCost -> EqualCost $cpred :: EqualCost -> EqualCost pred :: EqualCost -> EqualCost $ctoEnum :: Int -> EqualCost toEnum :: Int -> EqualCost $cfromEnum :: EqualCost -> Int fromEnum :: EqualCost -> Int $cenumFrom :: EqualCost -> [EqualCost] enumFrom :: EqualCost -> [EqualCost] $cenumFromThen :: EqualCost -> EqualCost -> [EqualCost] enumFromThen :: EqualCost -> EqualCost -> [EqualCost] $cenumFromTo :: EqualCost -> EqualCost -> [EqualCost] enumFromTo :: EqualCost -> EqualCost -> [EqualCost] $cenumFromThenTo :: EqualCost -> EqualCost -> EqualCost -> [EqualCost] enumFromThenTo :: EqualCost -> EqualCost -> EqualCost -> [EqualCost] Enum,EqualCost EqualCost -> EqualCost -> Bounded EqualCost forall a. a -> a -> Bounded a $cminBound :: EqualCost minBound :: EqualCost $cmaxBound :: EqualCost maxBound :: EqualCost Bounded)fileStoredValue ::ShakeOptions ->FileQ ->IO(MaybeFileA )fileStoredValue :: ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions {shakeChange :: ShakeOptions -> Change shakeChange =Change c ,shakeNeedDirectory :: ShakeOptions -> Bool shakeNeedDirectory =Bool allowDir }(FileQ FileName x )=doMaybe (ModTime, FileSize) res <-Bool -> FileName -> IO (Maybe (ModTime, FileSize)) getFileInfo Bool allowDir FileName x caseMaybe (ModTime, FileSize) res ofMaybe (ModTime, FileSize) Nothing->Maybe FileA -> IO (Maybe FileA) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pureMaybe FileA forall a. Maybe a NothingJust(ModTime time ,FileSize size )|Change c Change -> Change -> Bool forall a. Eq a => a -> a -> Bool ==Change ChangeModtime ->Maybe FileA -> IO (Maybe FileA) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure(Maybe FileA -> IO (Maybe FileA)) -> Maybe FileA -> IO (Maybe FileA) forall a b. (a -> b) -> a -> b $FileA -> Maybe FileA forall a. a -> Maybe a Just(FileA -> Maybe FileA) -> FileA -> Maybe FileA forall a b. (a -> b) -> a -> b $ModTime -> FileSize -> FileHash -> FileA FileA ModTime time FileSize size FileHash noFileHash Just(ModTime time ,FileSize size )->doFileHash hash <-IO FileHash -> IO FileHash forall a. IO a -> IO a unsafeInterleaveIO(IO FileHash -> IO FileHash) -> IO FileHash -> IO FileHash forall a b. (a -> b) -> a -> b $FileName -> IO FileHash getFileHash FileName x Maybe FileA -> IO (Maybe FileA) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure(Maybe FileA -> IO (Maybe FileA)) -> Maybe FileA -> IO (Maybe FileA) forall a b. (a -> b) -> a -> b $FileA -> Maybe FileA forall a. a -> Maybe a Just(FileA -> Maybe FileA) -> FileA -> Maybe FileA 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 )=caseChange c ofChange ChangeModtime ->Bool -> EqualCost bool (Bool -> EqualCost) -> Bool -> EqualCost forall a b. (a -> b) -> a -> b $ModTime x1 ModTime -> ModTime -> Bool forall a. Eq a => a -> a -> Bool ==ModTime y1 Change ChangeDigest ->Bool -> EqualCost bool (Bool -> EqualCost) -> Bool -> EqualCost forall a b. (a -> b) -> a -> b $FileSize x2 FileSize -> FileSize -> Bool forall a. Eq a => a -> a -> Bool ==FileSize y2 Bool -> Bool -> Bool &&FileHash x3 FileHash -> FileHash -> Bool forall a. Eq a => a -> a -> Bool ==FileHash y3 Change ChangeModtimeOrDigest ->Bool -> EqualCost bool (Bool -> EqualCost) -> Bool -> EqualCost forall a b. (a -> b) -> a -> b $ModTime x1 ModTime -> ModTime -> Bool forall a. Eq a => a -> a -> Bool ==ModTime y1 Bool -> Bool -> Bool &&FileSize x2 FileSize -> FileSize -> Bool forall a. Eq a => a -> a -> Bool ==FileSize y2 Bool -> Bool -> Bool &&FileHash x3 FileHash -> FileHash -> Bool forall a. Eq a => a -> a -> Bool ==FileHash y3 Change _|ModTime x1 ModTime -> ModTime -> Bool forall a. Eq a => a -> a -> Bool ==ModTime y1 ->EqualCost EqualCheap |FileSize x2 FileSize -> FileSize -> Bool forall a. Eq a => a -> a -> Bool ==FileSize y2 Bool -> Bool -> Bool &&FileHash x3 FileHash -> FileHash -> Bool forall a. Eq a => a -> a -> Bool ==FileHash y3 ->EqualCost EqualExpensive |Bool otherwise->EqualCost NotEqual wherebool :: Bool -> EqualCost bool Bool b =ifBool b thenEqualCost EqualCheap elseEqualCost NotEqual -- | Arguments: options; is the file an input; a message for failure if the file does not exist; filenamestoredValueError ::ShakeOptions ->Bool->String->FileQ ->IO(MaybeFileA ){- 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 =Maybe FileA -> (FileA -> Maybe FileA) -> Maybe FileA -> Maybe FileA forall b a. b -> (a -> b) -> Maybe a -> b maybeMaybe FileA def FileA -> Maybe FileA forall a. a -> Maybe a Just(Maybe FileA -> Maybe FileA) -> IO (Maybe FileA) -> IO (Maybe FileA) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts2 FileQ x wheredef :: Maybe FileA def =ifShakeOptions -> Bool shakeCreationCheck ShakeOptions opts Bool -> Bool -> Bool ||Bool input thenFilePath -> Maybe FileA forall a. HasCallStack => FilePath -> a errorFilePath err elseMaybe FileA forall a. Maybe a Nothingerr :: FilePath err =FilePath msg FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath "\n "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FileName -> FilePath fileNameToString (FileQ -> FileName fromFileQ FileQ x )opts2 :: ShakeOptions opts2 =ifBool -> Bool notBool input Bool -> Bool -> Bool &&ShakeOptions -> Change shakeChange ShakeOptions opts Change -> Change -> Bool forall a. Eq a => a -> a -> Bool ==Change ChangeModtimeAndDigestInput thenShakeOptions opts {shakeChange =ChangeModtime }elseShakeOptions opts ----------------------------------------------------------------------- THE DEFAULT RULEdefaultRuleFile ::Rules ()defaultRuleFile :: Rules () defaultRuleFile =doopts :: 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 () shakeChange :: ShakeOptions -> Change shakeNeedDirectory :: ShakeOptions -> Bool shakeCreationCheck :: ShakeOptions -> Bool shakeFiles :: FilePath shakeThreads :: Int shakeVersion :: FilePath shakeVerbosity :: Verbosity shakeStaunch :: Bool shakeReport :: [FilePath] shakeLint :: Maybe Lint shakeLintInside :: [FilePath] shakeLintIgnore :: [FilePath] shakeLintWatch :: [FilePath] shakeCommandOptions :: [CmdOption] shakeFlush :: Maybe Seconds shakeRebuild :: [(Rebuild, FilePath)] shakeAbbreviations :: [(FilePath, FilePath)] shakeStorageLog :: Bool shakeLineBuffering :: Bool shakeTimings :: Bool shakeRunCommands :: Bool shakeChange :: Change shakeCreationCheck :: Bool shakeLiveFiles :: [FilePath] shakeVersionIgnore :: Bool shakeColor :: Bool shakeShare :: Maybe FilePath shakeCloud :: [FilePath] shakeSymlink :: Bool shakeNeedDirectory :: Bool shakeAllowRedefineRules :: Bool shakeProgress :: IO Progress -> IO () shakeOutput :: Verbosity -> FilePath -> IO () shakeTrace :: FilePath -> FilePath -> Bool -> IO () shakeExtra :: HashMap TypeRep Dynamic shakeFiles :: ShakeOptions -> FilePath shakeThreads :: ShakeOptions -> Int shakeVersion :: ShakeOptions -> FilePath shakeVerbosity :: ShakeOptions -> Verbosity shakeStaunch :: ShakeOptions -> Bool shakeReport :: ShakeOptions -> [FilePath] shakeLint :: ShakeOptions -> Maybe Lint shakeLintInside :: ShakeOptions -> [FilePath] shakeLintIgnore :: ShakeOptions -> [FilePath] shakeLintWatch :: ShakeOptions -> [FilePath] shakeCommandOptions :: ShakeOptions -> [CmdOption] shakeFlush :: ShakeOptions -> Maybe Seconds shakeRebuild :: ShakeOptions -> [(Rebuild, FilePath)] shakeAbbreviations :: ShakeOptions -> [(FilePath, FilePath)] shakeStorageLog :: ShakeOptions -> Bool shakeLineBuffering :: ShakeOptions -> Bool shakeTimings :: ShakeOptions -> Bool shakeRunCommands :: ShakeOptions -> Bool shakeLiveFiles :: ShakeOptions -> [FilePath] shakeVersionIgnore :: ShakeOptions -> Bool shakeColor :: ShakeOptions -> Bool shakeShare :: ShakeOptions -> Maybe FilePath shakeCloud :: ShakeOptions -> [FilePath] shakeSymlink :: ShakeOptions -> Bool shakeAllowRedefineRules :: ShakeOptions -> Bool shakeProgress :: ShakeOptions -> IO Progress -> IO () shakeOutput :: ShakeOptions -> Verbosity -> FilePath -> IO () shakeTrace :: ShakeOptions -> FilePath -> FilePath -> Bool -> IO () shakeExtra :: ShakeOptions -> HashMap TypeRep Dynamic .. }<-Rules ShakeOptions getShakeOptionsRules -- A rule from FileQ to (Maybe FileA). The result value is only useful for linting.BuiltinLint FileQ FileR -> BuiltinIdentity FileQ FileR -> BuiltinRun FileQ FileR -> Rules () 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 ((FilePath -> Rebuild) -> BuiltinRun FileQ FileR) -> (FilePath -> Rebuild) -> BuiltinRun FileQ FileR 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 (JustFileA v )Bool True)=doMaybe FileA now <-ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts FileQ k Maybe FilePath -> IO (Maybe FilePath) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure(Maybe FilePath -> IO (Maybe FilePath)) -> Maybe FilePath -> IO (Maybe FilePath) forall a b. (a -> b) -> a -> b $caseMaybe FileA now ofMaybe FileA Nothing->FilePath -> Maybe FilePath forall a. a -> Maybe a JustFilePath "<missing>"JustFileA now |ShakeOptions -> FileA -> FileA -> EqualCost fileEqualValue ShakeOptions opts FileA v FileA now EqualCost -> EqualCost -> Bool forall a. Eq a => a -> a -> Bool ==EqualCost EqualCheap ->Maybe FilePath forall a. Maybe a Nothing|Bool otherwise->FilePath -> Maybe FilePath forall a. a -> Maybe a Just(FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath forall a b. (a -> b) -> a -> b $FileA -> FilePath forall a. Show a => a -> FilePath showFileA now ruleLint ShakeOptions _FileQ _FileR _=Maybe FilePath -> IO (Maybe FilePath) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pureMaybe FilePath forall a. Maybe a NothingruleIdentity ::ShakeOptions ->BuiltinIdentity FileQ FileR ruleIdentity :: ShakeOptions -> BuiltinIdentity FileQ FileR ruleIdentity ShakeOptions opts |ShakeOptions -> Change shakeChange ShakeOptions opts Change -> Change -> Bool forall a. Eq a => a -> a -> Bool ==Change ChangeModtime =SomeException -> BuiltinIdentity FileQ FileR forall a. SomeException -> a throwImpure SomeException errorNoHash ruleIdentity ShakeOptions _=\FileQ k FileR v ->caseFileR -> Maybe FileA answer FileR v ofJust(FileA ModTime _FileSize size FileHash hash )->ByteString -> Maybe ByteString forall a. a -> Maybe a Just(ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString forall a b. (a -> b) -> a -> b $Builder -> ByteString runBuilder (Builder -> ByteString) -> Builder -> ByteString forall a b. (a -> b) -> a -> b $FileSize -> Builder forall a. Storable a => a -> Builder putExStorable FileSize size Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <>FileHash -> Builder forall a. Storable a => a -> Builder putExStorable FileHash hash Maybe FileA Nothing->Maybe ByteString forall a. Maybe a NothingruleRun ::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 () shakeChange :: ShakeOptions -> Change shakeNeedDirectory :: ShakeOptions -> Bool shakeCreationCheck :: ShakeOptions -> Bool shakeFiles :: ShakeOptions -> FilePath shakeThreads :: ShakeOptions -> Int shakeVersion :: ShakeOptions -> FilePath shakeVerbosity :: ShakeOptions -> Verbosity shakeStaunch :: ShakeOptions -> Bool shakeReport :: ShakeOptions -> [FilePath] shakeLint :: ShakeOptions -> Maybe Lint shakeLintInside :: ShakeOptions -> [FilePath] shakeLintIgnore :: ShakeOptions -> [FilePath] shakeLintWatch :: ShakeOptions -> [FilePath] shakeCommandOptions :: ShakeOptions -> [CmdOption] shakeFlush :: ShakeOptions -> Maybe Seconds shakeRebuild :: ShakeOptions -> [(Rebuild, FilePath)] shakeAbbreviations :: ShakeOptions -> [(FilePath, FilePath)] shakeStorageLog :: ShakeOptions -> Bool shakeLineBuffering :: ShakeOptions -> Bool shakeTimings :: ShakeOptions -> Bool shakeRunCommands :: ShakeOptions -> Bool shakeLiveFiles :: ShakeOptions -> [FilePath] shakeVersionIgnore :: ShakeOptions -> Bool shakeColor :: ShakeOptions -> Bool shakeShare :: ShakeOptions -> Maybe FilePath shakeCloud :: ShakeOptions -> [FilePath] shakeSymlink :: ShakeOptions -> Bool shakeAllowRedefineRules :: ShakeOptions -> Bool shakeProgress :: ShakeOptions -> IO Progress -> IO () shakeOutput :: ShakeOptions -> Verbosity -> FilePath -> IO () shakeTrace :: ShakeOptions -> FilePath -> FilePath -> Bool -> IO () shakeExtra :: ShakeOptions -> HashMap TypeRep Dynamic shakeFiles :: FilePath shakeThreads :: Int shakeVersion :: FilePath shakeVerbosity :: Verbosity shakeStaunch :: Bool shakeReport :: [FilePath] shakeLint :: Maybe Lint shakeLintInside :: [FilePath] shakeLintIgnore :: [FilePath] shakeLintWatch :: [FilePath] shakeCommandOptions :: [CmdOption] shakeFlush :: Maybe Seconds shakeRebuild :: [(Rebuild, FilePath)] shakeAbbreviations :: [(FilePath, FilePath)] shakeStorageLog :: Bool shakeLineBuffering :: Bool shakeTimings :: Bool shakeRunCommands :: Bool shakeChange :: Change shakeCreationCheck :: Bool shakeLiveFiles :: [FilePath] shakeVersionIgnore :: Bool shakeColor :: Bool shakeShare :: Maybe FilePath shakeCloud :: [FilePath] shakeSymlink :: Bool shakeNeedDirectory :: Bool shakeAllowRedefineRules :: Bool shakeProgress :: IO Progress -> IO () shakeOutput :: Verbosity -> FilePath -> IO () shakeTrace :: FilePath -> FilePath -> Bool -> IO () shakeExtra :: HashMap TypeRep Dynamic .. }FilePath -> Rebuild rebuildFlags o :: FileQ o @(FileQ (FileName -> FilePath fileNameToString ->FilePath xStr ))oldBin :: Maybe ByteString oldBin @((ByteString -> Answer) -> Maybe ByteString -> Maybe Answer forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmapByteString -> Answer forall a. BinaryEx a => ByteString -> a getEx ->Maybe Answer old ::MaybeAnswer )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?letr :: Rebuild r =FilePath -> Rebuild rebuildFlags FilePath xStr (Maybe Ver ruleVer ,[(Int, Mode)] ruleAct ,SomeException ruleErr )<-FileQ -> (FileRule -> Maybe FilePath) -> (FileRule -> Maybe Mode) -> Action (Maybe Ver, [(Int, Mode)], SomeException) 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 _)->FilePath -> Maybe FilePath forall a. a -> Maybe a JustFilePath s )((FileRule -> Maybe Mode) -> Action (Maybe Ver, [(Int, Mode)], SomeException)) -> (FileRule -> Maybe Mode) -> Action (Maybe Ver, [(Int, Mode)], SomeException) forall a b. (a -> b) -> a -> b $\(FileRule FilePath _FilePath -> Maybe Mode f )->FilePath -> Maybe Mode f FilePath xStr letverEq :: Ver -> Bool verEq Ver v =Ver -> Maybe Ver forall a. a -> Maybe a JustVer v Maybe Ver -> Maybe Ver -> Bool forall a. Eq a => a -> a -> Bool ==Maybe Ver ruleVer Bool -> Bool -> Bool ||case[(Int, Mode)] ruleAct of[]->Ver v Ver -> Ver -> Bool forall a. Eq a => a -> a -> Bool ==Int -> Ver Ver Int 0;[(Int v2 ,Mode _)]->Ver v Ver -> Ver -> Bool forall a. Eq a => a -> a -> Bool ==Int -> Ver Ver Int v2 ;[(Int, Mode)] _->Bool Falseletrebuild :: Action (RunResult FileR) rebuild =doVerbosity -> FilePath -> Action () putWhen Verbosity Verbose (FilePath -> Action ()) -> FilePath -> Action () forall a b. (a -> b) -> a -> b $FilePath "# "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FileQ -> FilePath forall a. Show a => a -> FilePath showFileQ o case[(Int, Mode)] ruleAct of[]->Maybe (Int, Mode) -> Action (RunResult FileR) rebuildWith Maybe (Int, Mode) forall a. Maybe a Nothing[(Int, Mode) x ]->Maybe (Int, Mode) -> Action (RunResult FileR) rebuildWith (Maybe (Int, Mode) -> Action (RunResult FileR)) -> Maybe (Int, Mode) -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $(Int, Mode) -> Maybe (Int, Mode) forall a. a -> Maybe a Just(Int, Mode) x [(Int, Mode)] _->SomeException -> Action (RunResult FileR) forall (m :: * -> *) a. MonadIO m => SomeException -> m a throwM SomeException ruleErr caseMaybe Answer old ofMaybe Answer _|Rebuild r Rebuild -> Rebuild -> Bool forall a. Eq a => a -> a -> Bool ==Rebuild RebuildNow ->Action (RunResult FileR) rebuild Maybe Answer _|Rebuild r Rebuild -> Rebuild -> Bool forall a. Eq a => a -> a -> Bool ==Rebuild RebuildLater ->caseMaybe Answer old ofJustAnswer _->-- ignoring the currently stored value, which may trigger lint has changed-- so disable lint on this fileRunResult FileR -> RunResult FileR unLint (RunResult FileR -> RunResult FileR) -> Action (RunResult FileR) -> Action (RunResult FileR) 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 futureMaybe FileA now <-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts FileQ o caseMaybe FileA now ofMaybe FileA Nothing->Action (RunResult FileR) rebuild JustFileA now ->doAction () alwaysRerun ;RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged ChangedStore (Answer -> Action (RunResult FileR)) -> Answer -> Action (RunResult FileR) 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 RunMode -> RunMode -> Bool forall a. Eq a => a -> a -> Bool ==RunMode RunDependenciesSame ,Ver -> Bool verEq Ver ver ->doMaybe FileA now <-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts FileQ o letnoHash :: FileA -> Bool noHash (FileA ModTime _FileSize _FileHash x )=FileHash -> Bool isNoFileHash FileHash x caseMaybe FileA now ofMaybe FileA Nothing->Action (RunResult FileR) rebuild JustFileA now ->caseShakeOptions -> FileA -> FileA -> EqualCost fileEqualValue ShakeOptions opts FileA old FileA now ofEqualCost NotEqual ->Action (RunResult FileR) rebuild -- if our last build used no file hashing, but this build should, then we must refresh the hashEqualCost EqualCheap |ifFileA -> Bool noHash FileA old thenChange shakeChange Change -> Change -> Bool forall a. Eq a => a -> a -> Bool ==Change ChangeModtimeAndDigestInput Bool -> Bool -> Bool ||FileA -> Bool noHash FileA now elseBool True->RunChanged -> Action (RunResult FileR) retOld RunChanged ChangedNothing EqualCost _->RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged ChangedStore (Answer -> Action (RunResult FileR)) -> Answer -> Action (RunResult FileR) 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 RunMode -> RunMode -> Bool 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 #427fileR :: Answer -> FileR fileR (AnswerDirect Ver _FileA x )=Maybe FileA -> Bool -> FileR FileR (FileA -> Maybe FileA forall a. a -> Maybe a JustFileA x )Bool TruefileR (AnswerForward Ver _FileA x )=Maybe FileA -> Bool -> FileR FileR (FileA -> Maybe FileA forall a. a -> Maybe a JustFileA x )Bool FalsefileR Answer AnswerPhony =Maybe FileA -> Bool -> FileR FileR Maybe FileA forall a. Maybe a NothingBool FalseunLint :: RunResult FileR -> RunResult FileR unLint (RunResult RunChanged a ByteString b FileR c )=RunChanged -> ByteString -> FileR -> RunResult FileR forall value. RunChanged -> ByteString -> value -> RunResult value RunResult RunChanged a ByteString b FileR c {useLint =False}retNew ::RunChanged ->Answer ->Action (RunResult FileR )retNew :: RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged c Answer v =RunResult FileR -> Action (RunResult FileR) forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure(RunResult FileR -> Action (RunResult FileR)) -> RunResult FileR -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $RunChanged -> ByteString -> FileR -> RunResult FileR forall value. RunChanged -> ByteString -> value -> RunResult value RunResult RunChanged c (Builder -> ByteString runBuilder (Builder -> ByteString) -> Builder -> ByteString forall a b. (a -> b) -> a -> b $Answer -> Builder forall a. BinaryEx a => a -> Builder putEx Answer v )(FileR -> RunResult FileR) -> FileR -> RunResult FileR 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 =RunResult FileR -> Action (RunResult FileR) forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure(RunResult FileR -> Action (RunResult FileR)) -> RunResult FileR -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $RunChanged -> ByteString -> FileR -> RunResult FileR forall value. RunChanged -> ByteString -> value -> RunResult value RunResult RunChanged c (Maybe ByteString -> ByteString forall a. HasCallStack => Maybe a -> a fromJustMaybe ByteString oldBin )(FileR -> RunResult FileR) -> FileR -> RunResult FileR forall a b. (a -> b) -> a -> b $Answer -> FileR fileR (Maybe Answer -> Answer forall a. HasCallStack => Maybe a -> a fromJustMaybe Answer old )-- actually run the rebuildrebuildWith :: Maybe (Int, Mode) -> Action (RunResult FileR) rebuildWith Maybe (Int, Mode) act =doletanswer :: (FileA -> Answer) -> FileA -> Action (RunResult FileR) answer FileA -> Answer ctor FileA new =doletb :: RunChanged b =case()of() _|JustAnswer old <-Maybe Answer old ,JustFileA old <-Answer -> Maybe FileA fromAnswer Answer old ,ShakeOptions -> FileA -> FileA -> EqualCost fileEqualValue ShakeOptions opts FileA old FileA new EqualCost -> EqualCost -> Bool forall a. Eq a => a -> a -> Bool /=EqualCost NotEqual ->RunChanged ChangedRecomputeSame () _->RunChanged ChangedRecomputeDiff RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged b (Answer -> Action (RunResult FileR)) -> Answer -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $FileA -> Answer ctor FileA new caseMaybe (Int, Mode) act ofMaybe (Int, Mode) Nothing->doMaybe FileA new <-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA) storedValueError ShakeOptions opts Bool TrueFilePath "Error, file does not exist and no rule available:"FileQ o (FileA -> Answer) -> FileA -> Action (RunResult FileR) answer (Ver -> FileA -> Answer AnswerDirect (Ver -> FileA -> Answer) -> Ver -> FileA -> Answer forall a b. (a -> b) -> a -> b $Int -> Ver Ver Int 0)(FileA -> Action (RunResult FileR)) -> FileA -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $Maybe FileA -> FileA forall a. HasCallStack => Maybe a -> a fromJustMaybe FileA new Just(Int ver ,ModeForward Action (Maybe FileA) act )->doMaybe FileA new <-Action (Maybe FileA) act caseMaybe FileA new ofMaybe FileA Nothing->do-- Not 100% sure how you get here, but I think it involves RebuildLater and multi-file rulesAction () historyDisable RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged ChangedRecomputeDiff Answer AnswerPhony JustFileA new ->(FileA -> Answer) -> FileA -> Action (RunResult FileR) answer (Ver -> FileA -> Answer AnswerForward (Ver -> FileA -> Answer) -> Ver -> FileA -> Answer forall a b. (a -> b) -> a -> b $Int -> Ver Ver Int ver )FileA new Just(Int ver ,ModeDirect Action () act )->doMaybe ByteString cache <-Int -> Action (Maybe ByteString) historyLoad Int ver caseMaybe ByteString cache ofJustByteString encodedHash ->doJust(FileA ModTime mod FileSize size FileHash _)<-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA) storedValueError ShakeOptions opts Bool FalseFilePath "Error, restored the rule but did not produce file:"FileQ o (FileA -> Answer) -> FileA -> Action (RunResult FileR) answer (Ver -> FileA -> Answer AnswerDirect (Ver -> FileA -> Answer) -> Ver -> FileA -> Answer forall a b. (a -> b) -> a -> b $Int -> Ver Ver Int ver )(FileA -> Action (RunResult FileR)) -> FileA -> Action (RunResult FileR) forall a b. (a -> b) -> a -> b $ModTime -> FileSize -> FileHash -> FileA FileA ModTime mod FileSize size (FileHash -> FileA) -> FileHash -> FileA forall a b. (a -> b) -> a -> b $ByteString -> FileHash forall a. Storable a => ByteString -> a getExStorable ByteString encodedHash Maybe ByteString Nothing->doAction () act Maybe FileA new <-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> Bool -> FilePath -> FileQ -> IO (Maybe FileA) storedValueError ShakeOptions opts Bool FalseFilePath "Error, rule finished running but did not produce file:"FileQ o caseMaybe FileA new ofMaybe 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 botherAction () historyDisable RunChanged -> Answer -> Action (RunResult FileR) retNew RunChanged ChangedRecomputeDiff Answer AnswerPhony Justnew :: 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 (Ver -> FileA -> Answer) -> Ver -> FileA -> Answer forall a b. (a -> b) -> a -> b $Int -> Ver Ver Int ver )FileA new Int -> ByteString -> Action () historySave Int ver (ByteString -> Action ()) -> ByteString -> Action () forall a b. (a -> b) -> a -> b $Builder -> ByteString runBuilder (Builder -> ByteString) -> Builder -> ByteString forall a b. (a -> b) -> a -> b $ifFileHash -> Bool isNoFileHash FileHash fileHash thenSomeException -> Builder forall a. SomeException -> a throwImpure SomeException errorNoHash elseFileHash -> Builder forall a. Storable a => a -> Builder putExStorable FileHash fileHash RunResult FileR -> Action (RunResult FileR) forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pureRunResult 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 =[FileQ] -> Action [FileR] forall key value. (HasCallStack, RuleResult key ~ value, ShakeValue key, Typeable value) => [key] -> Action [value] apply ([FileQ] -> Action [FileR]) -> ([a] -> [FileQ]) -> [a] -> Action [FileR] forall b c a. (b -> c) -> (a -> b) -> a -> c .(a -> FileQ) -> [a] -> [FileQ] forall a b. (a -> b) -> [a] -> [b] map(FileName -> FileQ FileQ (FileName -> FileQ) -> (a -> FileName) -> a -> 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 BoolresultHasChanged :: FilePath -> Action Bool resultHasChanged FilePath file =doletfilename :: FileQ filename =FileName -> FileQ FileQ (FileName -> FileQ) -> FileName -> FileQ forall a b. (a -> b) -> a -> b $FilePath -> FileName fileNameFromString FilePath file Maybe (Result (Either ByteString FileR)) res <-FileQ -> Action (Maybe (Result (Either ByteString FileR))) forall key value. (RuleResult key ~ value, ShakeValue key, Typeable value) => key -> Action (Maybe (Result (Either ByteString value))) getDatabaseValue FileQ filename Maybe FileA old <-Maybe FileA -> Action (Maybe FileA) forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure(Maybe FileA -> Action (Maybe FileA)) -> Maybe FileA -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $caseResult (Either ByteString FileR) -> Either ByteString FileR forall a. Result a -> a result (Result (Either ByteString FileR) -> Either ByteString FileR) -> Maybe (Result (Either ByteString FileR)) -> Maybe (Either ByteString FileR) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>Maybe (Result (Either ByteString FileR)) res ofMaybe (Either ByteString FileR) Nothing->Maybe FileA forall a. Maybe a NothingJust(LeftByteString bs )->Answer -> Maybe FileA fromAnswer (Answer -> Maybe FileA) -> Answer -> Maybe FileA forall a b. (a -> b) -> a -> b $ByteString -> Answer forall a. BinaryEx a => ByteString -> a getEx ByteString bs Just(RightFileR v )->FileR -> Maybe FileA answer FileR v caseMaybe FileA old ofMaybe FileA Nothing->Bool -> Action Bool forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pureBool TrueJustFileA old ->doShakeOptions opts <-Action ShakeOptions getShakeOptions Maybe FileA new <-IO (Maybe FileA) -> Action (Maybe FileA) forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO (Maybe FileA) -> Action (Maybe FileA)) -> IO (Maybe FileA) -> Action (Maybe FileA) forall a b. (a -> b) -> a -> b $ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts FileQ filename Bool -> Action Bool forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure(Bool -> Action Bool) -> Bool -> Action Bool forall a b. (a -> b) -> a -> b $caseMaybe FileA new ofMaybe FileA Nothing->Bool TrueJustFileA new ->ShakeOptions -> FileA -> FileA -> EqualCost fileEqualValue ShakeOptions opts FileA old FileA new EqualCost -> EqualCost -> Bool forall a. Eq a => a -> a -> Bool ==EqualCost NotEqual ----------------------------------------------------------------------- OPTIONS ON TOP-- | Internal method for adding forwarding actionsfileForward ::String->(FilePath->Maybe(Action (MaybeFileA )))->Rules ()fileForward :: FilePath -> (FilePath -> Maybe (Action (Maybe FileA))) -> Rules () fileForward FilePath help FilePath -> Maybe (Action (Maybe FileA)) act =FileRule -> Rules () forall a. Typeable a => a -> Rules () addUserRule (FileRule -> Rules ()) -> FileRule -> Rules () forall a b. (a -> b) -> a -> b $FilePath -> (FilePath -> Maybe Mode) -> FileRule FileRule FilePath help ((FilePath -> Maybe Mode) -> FileRule) -> (FilePath -> Maybe Mode) -> FileRule forall a b. (a -> b) -> a -> b $(Action (Maybe FileA) -> Mode) -> Maybe (Action (Maybe FileA)) -> Maybe Mode forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmapAction (Maybe FileA) -> Mode ModeForward (Maybe (Action (Maybe FileA)) -> Maybe Mode) -> (FilePath -> Maybe (Action (Maybe FileA))) -> FilePath -> Maybe Mode 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 =(HasCallStack => [FilePath] -> Action ()) -> [FilePath] -> Action () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => [FilePath] -> Action ()) -> [FilePath] -> Action ()) -> (HasCallStack => [FilePath] -> Action ()) -> [FilePath] -> Action () forall a b. (a -> b) -> a -> b $Action [FileR] -> Action () forall (f :: * -> *) a. Functor f => f a -> f () void(Action [FileR] -> Action ()) -> ([FilePath] -> Action [FileR]) -> [FilePath] -> Action () forall b c a. (b -> c) -> (a -> b) -> a -> c .(FilePath -> FileName) -> [FilePath] -> Action [FileR] 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 =(HasCallStack => Action [FilePath]) -> Action [FilePath] forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Action [FilePath]) -> Action [FilePath]) -> (HasCallStack => Action [FilePath]) -> Action [FilePath] forall a b. (a -> b) -> a -> b $do(FilePath -> FileName) -> [FilePath] -> Action [FileR] 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 <-caseMaybe Key self ofMaybe Key Nothing->Maybe (Result (Either ByteString Value)) -> Action (Maybe (Result (Either ByteString Value))) forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pureMaybe (Result (Either ByteString Value)) forall a. Maybe a NothingJustKey self ->Key -> Action (Maybe (Result (Either ByteString Value))) getDatabaseValueGeneric Key self caseMaybe (Result (Either ByteString Value)) selfVal ofMaybe (Result (Either ByteString Value)) Nothing->[FilePath] -> Action [FilePath] forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure[FilePath] paths -- never build before or not a key, so everything has changedJustResult (Either ByteString Value) selfVal ->((FilePath -> Action Bool) -> [FilePath] -> Action [FilePath]) -> [FilePath] -> (FilePath -> Action Bool) -> Action [FilePath] forall a b c. (a -> b -> c) -> b -> a -> c flip(FilePath -> Action Bool) -> [FilePath] -> Action [FilePath] forall (m :: * -> *) a. Applicative m => (a -> m Bool) -> [a] -> m [a] filterM[FilePath] paths ((FilePath -> Action Bool) -> Action [FilePath]) -> (FilePath -> Action Bool) -> Action [FilePath] forall a b. (a -> b) -> a -> b $\FilePath path ->doMaybe (Result (Either ByteString FileR)) pathVal <-FileQ -> Action (Maybe (Result (Either ByteString FileR))) forall key value. (RuleResult key ~ value, ShakeValue key, Typeable value) => key -> Action (Maybe (Result (Either ByteString value))) getDatabaseValue (FileName -> FileQ FileQ (FileName -> FileQ) -> FileName -> FileQ forall a b. (a -> b) -> a -> b $FilePath -> FileName fileNameFromString FilePath path )Bool -> Action Bool forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure(Bool -> Action Bool) -> Bool -> Action Bool forall a b. (a -> b) -> a -> b $caseMaybe (Result (Either ByteString FileR)) pathVal ofJustResult (Either ByteString FileR) pathVal |Result (Either ByteString FileR) -> Step forall a. Result a -> Step changed Result (Either ByteString FileR) pathVal Step -> Step -> Bool forall a. Ord a => a -> a -> Bool >Result (Either ByteString Value) -> Step forall a. Result a -> Step built Result (Either ByteString Value) selfVal ->Bool TrueMaybe (Result (Either ByteString FileR)) _->Bool FalseneedBS ::Partial=>[BS.ByteString]->Action ()needBS :: HasCallStack => [ByteString] -> Action () needBS =(HasCallStack => [ByteString] -> Action ()) -> [ByteString] -> Action () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => [ByteString] -> Action ()) -> [ByteString] -> Action ()) -> (HasCallStack => [ByteString] -> Action ()) -> [ByteString] -> Action () forall a b. (a -> b) -> a -> b $Action [FileR] -> Action () forall (f :: * -> *) a. Functor f => f a -> f () void(Action [FileR] -> Action ()) -> ([ByteString] -> Action [FileR]) -> [ByteString] -> Action () forall b c a. (b -> c) -> (a -> b) -> a -> c .(ByteString -> FileName) -> [ByteString] -> Action [FileR] 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 =(HasCallStack => Action ()) -> Action () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Action ()) -> Action ()) -> (HasCallStack => Action ()) -> Action () forall a b. (a -> b) -> a -> b $doShakeOptions opts <-Action ShakeOptions getShakeOptions ifMaybe Lint -> Bool forall a. Maybe a -> Bool isNothing(Maybe Lint -> Bool) -> Maybe Lint -> Bool forall a b. (a -> b) -> a -> b $ShakeOptions -> Maybe Lint shakeLint ShakeOptions opts thenHasCallStack => [FilePath] -> Action () [FilePath] -> Action () need [FilePath] xs elseHasCallStack => [FileName] -> Action () [FileName] -> Action () neededCheck ([FileName] -> Action ()) -> [FileName] -> Action () forall a b. (a -> b) -> a -> b $(FilePath -> FileName) -> [FilePath] -> [FileName] forall a b. (a -> b) -> [a] -> [b] mapFilePath -> FileName fileNameFromString [FilePath] xs neededBS ::Partial=>[BS.ByteString]->Action ()neededBS :: HasCallStack => [ByteString] -> Action () neededBS [ByteString] xs =(HasCallStack => Action ()) -> Action () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Action ()) -> Action ()) -> (HasCallStack => Action ()) -> Action () forall a b. (a -> b) -> a -> b $doShakeOptions opts <-Action ShakeOptions getShakeOptions ifMaybe Lint -> Bool forall a. Maybe a -> Bool isNothing(Maybe Lint -> Bool) -> Maybe Lint -> Bool forall a b. (a -> b) -> a -> b $ShakeOptions -> Maybe Lint shakeLint ShakeOptions opts thenHasCallStack => [ByteString] -> Action () [ByteString] -> Action () needBS [ByteString] xs elseHasCallStack => [FileName] -> Action () [FileName] -> Action () neededCheck ([FileName] -> Action ()) -> [FileName] -> Action () forall a b. (a -> b) -> a -> b $(ByteString -> FileName) -> [ByteString] -> [FileName] forall a b. (a -> b) -> [a] -> [b] mapByteString -> FileName fileNameFromByteString [ByteString] xs neededCheck ::Partial=>[FileName ]->Action ()neededCheck :: HasCallStack => [FileName] -> Action () neededCheck [FileName] xs =(HasCallStack => Action ()) -> Action () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Action ()) -> Action ()) -> (HasCallStack => Action ()) -> Action () forall a b. (a -> b) -> a -> b $doShakeOptions opts <-Action ShakeOptions getShakeOptions [Maybe FileA] pre <-IO [Maybe FileA] -> Action [Maybe FileA] forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO [Maybe FileA] -> Action [Maybe FileA]) -> IO [Maybe FileA] -> Action [Maybe FileA] forall a b. (a -> b) -> a -> b $(FileName -> IO (Maybe FileA)) -> [FileName] -> IO [Maybe FileA] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] mapM(ShakeOptions -> FileQ -> IO (Maybe FileA) fileStoredValue ShakeOptions opts (FileQ -> IO (Maybe FileA)) -> (FileName -> FileQ) -> FileName -> IO (Maybe FileA) forall b c a. (b -> c) -> (a -> b) -> a -> c .FileName -> FileQ FileQ )[FileName] xs [FileR] post <-(FileName -> FileName) -> [FileName] -> Action [FileR] forall a. HasCallStack => (a -> FileName) -> [a] -> Action [FileR] apply_ FileName -> FileName forall a. a -> a id[FileName] xs letbad :: [(FileName, FilePath)] bad =[(FileName x ,ifMaybe FileA -> Bool forall a. Maybe a -> Bool isJustMaybe FileA a thenFilePath "File change"elseFilePath "File created")|(FileName x ,Maybe FileA a ,FileR (JustFileA b )Bool _)<-[FileName] -> [Maybe FileA] -> [FileR] -> [(FileName, Maybe FileA, FileR)] forall a b c. [a] -> [b] -> [c] -> [(a, b, c)] zip3[FileName] xs [Maybe FileA] pre [FileR] post ,EqualCost -> (FileA -> EqualCost) -> Maybe FileA -> EqualCost forall b a. b -> (a -> b) -> Maybe a -> b maybeEqualCost NotEqual (\FileA a ->ShakeOptions -> FileA -> FileA -> EqualCost fileEqualValue ShakeOptions opts FileA a FileA b )Maybe FileA a EqualCost -> EqualCost -> Bool forall a. Eq a => a -> a -> Bool ==EqualCost NotEqual ]case[(FileName, FilePath)] bad of[]->() -> Action () forall a. a -> Action a forall (f :: * -> *) a. Applicative f => a -> f a pure()(FileName file ,FilePath msg ):[(FileName, FilePath)] _->SomeException -> Action () forall (m :: * -> *) a. MonadIO m => SomeException -> m a throwM (SomeException -> Action ()) -> SomeException -> Action () forall a b. (a -> b) -> a -> b $FilePath -> [(FilePath, Maybe FilePath)] -> FilePath -> SomeException errorStructured FilePath "Lint checking error - 'needed' file required rebuilding"[(FilePath "File",FilePath -> Maybe FilePath forall a. a -> Maybe a Just(FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath forall a b. (a -> b) -> a -> b $FileName -> FilePath fileNameToString FileName file ),(FilePath "Error",FilePath -> Maybe FilePath forall a. a -> Maybe a JustFilePath msg )]FilePath ""-- Either trackRead or trackWritetrack ::([FileQ ]->Action ())->[FilePath]->Action ()track :: ([FileQ] -> Action ()) -> [FilePath] -> Action () track [FileQ] -> Action () tracker [FilePath] xs =doShakeOptions {[FilePath] shakeLintIgnore :: ShakeOptions -> [FilePath] shakeLintIgnore :: [FilePath] shakeLintIgnore }<-Action ShakeOptions getShakeOptions letignore :: FilePath -> Bool ignore =[FilePath] -> FilePath -> Bool (?==*) [FilePath] shakeLintIgnore letys :: [FilePath] ys =(FilePath -> Bool) -> [FilePath] -> [FilePath] forall a. (a -> Bool) -> [a] -> [a] filter(Bool -> Bool not(Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .FilePath -> Bool ignore )[FilePath] xs Bool -> Action () -> Action () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when([FilePath] ys [FilePath] -> [FilePath] -> Bool forall a. Eq a => a -> a -> Bool /=[])(Action () -> Action ()) -> Action () -> Action () forall a b. (a -> b) -> a -> b $[FileQ] -> Action () tracker ([FileQ] -> Action ()) -> [FileQ] -> Action () forall a b. (a -> b) -> a -> b $(FilePath -> FileQ) -> [FilePath] -> [FileQ] forall a b. (a -> b) -> [a] -> [b] map(FileName -> FileQ FileQ (FileName -> FileQ) -> (FilePath -> FileName) -> FilePath -> 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 [FileQ] -> Action () 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 [FileQ] -> Action () 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 =doletignore :: FilePath -> Bool ignore =[FilePath] -> FilePath -> Bool (?==*) [FilePath] ps (FileQ -> Bool) -> Action () forall key. ShakeValue key => (key -> Bool) -> Action () lintTrackAllow ((FileQ -> Bool) -> Action ()) -> (FileQ -> Bool) -> Action () forall a b. (a -> b) -> a -> b $\(FileQ FileName x )->FilePath -> Bool ignore (FilePath -> Bool) -> FilePath -> Bool 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 []=() -> Rules () forall a. a -> Rules a forall (f :: * -> *) a. Applicative f => a -> f a pure()want [FilePath] xs =(HasCallStack => Rules ()) -> Rules () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Rules ()) -> Rules ()) -> (HasCallStack => Rules ()) -> Rules () forall a b. (a -> b) -> a -> b $Action () -> Rules () forall a. HasCallStack => Action a -> Rules () action (Action () -> Rules ()) -> Action () -> Rules () forall a b. (a -> b) -> a -> b $HasCallStack => [FilePath] -> Action () [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 =FileRule -> Rules () forall a. Typeable a => a -> Rules () addUserRule (FileRule -> Rules ()) -> FileRule -> Rules () forall a b. (a -> b) -> a -> b $FilePath -> (FilePath -> Maybe Mode) -> FileRule FileRule FilePath help ((FilePath -> Maybe Mode) -> FileRule) -> (FilePath -> Maybe Mode) -> FileRule forall a b. (a -> b) -> a -> b $\FilePath x ->ifBool -> Bool not(Bool -> Bool) -> Bool -> Bool forall a b. (a -> b) -> a -> b $FilePath -> Bool test FilePath x thenMaybe Mode forall a. Maybe a NothingelseMode -> Maybe Mode forall a. a -> Maybe a Just(Mode -> Maybe Mode) -> Mode -> Maybe Mode forall a b. (a -> b) -> a -> b $Action () -> Mode ModeDirect (Action () -> Mode) -> Action () -> Mode forall a b. (a -> b) -> a -> b $doIO () -> Action () forall a. IO a -> Action a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO(IO () -> Action ()) -> IO () -> Action () forall a b. (a -> b) -> a -> b $FilePath -> IO () createDirectoryRecursive (FilePath -> IO ()) -> FilePath -> IO () forall a b. (a -> b) -> a -> b $ShowS takeDirectoryFilePath 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 =doFilePath -> Rules () addTarget FilePath oname FilePath -> (FilePath -> Maybe (Action ())) -> Rules () addPhony (FilePath "phony "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++ShowS forall a. Show a => a -> FilePath showFilePath oname FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath " at "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath HasCallStack => FilePath callStackTop )((FilePath -> Maybe (Action ())) -> Rules ()) -> (FilePath -> Maybe (Action ())) -> Rules () forall a b. (a -> b) -> a -> b $\FilePath s ->ifFilePath s FilePath -> FilePath -> Bool forall a. Eq a => a -> a -> Bool ==FilePath name thenAction () -> Maybe (Action ()) forall a. a -> Maybe a JustAction () act elseMaybe (Action ()) 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 "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath 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 =doFilePath -> Rules () addTarget FilePath oname FilePath -> (FilePath -> Maybe (Action ())) -> Rules () addPhony (ShowS forall a. Show a => a -> FilePath showFilePath oname FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath " ~> at "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath HasCallStack => FilePath callStackTop )((FilePath -> Maybe (Action ())) -> Rules ()) -> (FilePath -> Maybe (Action ())) -> Rules () forall a b. (a -> b) -> a -> b $\FilePath s ->ifFilePath s FilePath -> FilePath -> Bool forall a. Eq a => a -> a -> Bool ==FilePath name thenAction () -> Maybe (Action ()) forall a. a -> Maybe a JustAction () act elseMaybe (Action ()) forall a. Maybe a NothingaddPhony ::String->(String->Maybe(Action ()))->Rules ()addPhony :: FilePath -> (FilePath -> Maybe (Action ())) -> Rules () addPhony FilePath help FilePath -> Maybe (Action ()) act =FileRule -> Rules () forall a. Typeable a => a -> Rules () addUserRule (FileRule -> Rules ()) -> FileRule -> Rules () forall a b. (a -> b) -> a -> b $FilePath -> (FilePath -> Maybe Mode) -> FileRule FileRule FilePath help ((FilePath -> Maybe Mode) -> FileRule) -> (FilePath -> Maybe Mode) -> FileRule forall a b. (a -> b) -> a -> b $(Action () -> Mode) -> Maybe (Action ()) -> Maybe Mode forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmapAction () -> Mode ModePhony (Maybe (Action ()) -> Maybe Mode) -> (FilePath -> Maybe (Action ())) -> FilePath -> Maybe Mode 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 =Seconds -> Rules () -> Rules () forall a. Seconds -> Rules a -> Rules a priority Seconds 0.5(Rules () -> Rules ()) -> Rules () -> Rules () forall a b. (a -> b) -> a -> b $FilePath -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () root (FilePath "?> at "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath 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(FilePath -> Rules ()) -> [FilePath] -> Rules () 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 )=(FilePath -> Bool) -> [FilePath] -> ([FilePath], [FilePath]) forall a. (a -> Bool) -> [a] -> ([a], [a]) partitionFilePath -> Bool simple [FilePath] pats caseShowS -> [FilePath] -> [FilePath] forall a b. (a -> b) -> [a] -> [b] mapShowS toStandard [FilePath] simp of[]->() -> Rules () forall a. a -> Rules a 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 FilePath -> FilePath -> Bool forall a. Eq a => a -> a -> Bool ==FilePath p )FilePath -> Action () act [FilePath] ps ->letset :: HashSet FilePath set =[FilePath] -> HashSet FilePath forall a. (Eq a, Hashable a) => [a] -> HashSet a Set.fromList[FilePath] ps inFilePath -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () root FilePath help ((FilePath -> HashSet FilePath -> Bool) -> HashSet FilePath -> FilePath -> Bool forall a b c. (a -> b -> c) -> b -> a -> c flipFilePath -> HashSet FilePath -> Bool forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool Set.memberHashSet FilePath set (FilePath -> Bool) -> ShowS -> FilePath -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .ShowS toStandard )FilePath -> Action () act Bool -> Rules () -> Rules () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless([FilePath] -> Bool forall a. [a] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool null[FilePath] other )(Rules () -> Rules ()) -> Rules () -> Rules () forall a b. (a -> b) -> a -> b $letps :: [FilePath -> Bool] ps =(FilePath -> FilePath -> Bool) -> [FilePath] -> [FilePath -> Bool] forall a b. (a -> b) -> [a] -> [b] mapFilePath -> FilePath -> Bool (?==) [FilePath] other inSeconds -> Rules () -> Rules () forall a. Seconds -> Rules a -> Rules a priority Seconds 0.5(Rules () -> Rules ()) -> Rules () -> Rules () forall a b. (a -> b) -> a -> b $FilePath -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () root FilePath help (\FilePath x ->((FilePath -> Bool) -> Bool) -> [FilePath -> Bool] -> Bool forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool any((FilePath -> Bool) -> FilePath -> Bool forall a b. (a -> b) -> a -> b $FilePath x )[FilePath -> Bool] ps )FilePath -> Action () act wherehelp :: FilePath help =[FilePath] -> FilePath forall a. Show a => a -> FilePath show[FilePath] pats FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath " |%> at "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath 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 =(HasCallStack => Rules ()) -> Rules () forall a. HasCallStack => (HasCallStack => a) -> a withFrozenCallStack((HasCallStack => Rules ()) -> Rules ()) -> (HasCallStack => Rules ()) -> Rules () forall a b. (a -> b) -> a -> b $(ifFilePath -> Bool simple FilePath test thenRules () -> Rules () forall a. a -> a idelseSeconds -> Rules () -> Rules () forall a. Seconds -> Rules a -> Rules a priority Seconds 0.5)(Rules () -> Rules ()) -> Rules () -> Rules () forall a b. (a -> b) -> a -> b $doFilePath -> Rules () addTarget FilePath test FilePath -> (FilePath -> Bool) -> (FilePath -> Action ()) -> Rules () root (ShowS forall a. Show a => a -> FilePath showFilePath test FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath " %> at "FilePath -> ShowS forall a. [a] -> [a] -> [a] ++FilePath HasCallStack => FilePath callStackTop )(FilePath test FilePath -> FilePath -> Bool ?== )FilePath -> Action () act