{-# LANGUAGE ScopedTypeVariables #-}

module Development.Shake.Internal.Derived(
    copyFile', copyFileChanged,
    readFile', readFileLines,
    writeFile', writeFileLines, writeFileChanged,
    withTempFile, withTempDir,
    withTempFileWithin, withTempDirWithin,
    getHashedShakeVersion,
    getShakeExtra, getShakeExtraRules, addShakeExtra,
    par, forP,
    newResource, newThrottle, withResources,
    newCache
    ) where

import Control.Monad.Extra
import Control.Monad.IO.Class
import System.Directory
import System.FilePath (takeDirectory)
import System.IO (IOMode (..), hGetContents, withFile)
import qualified System.IO.Extra as IO

import Development.Shake.Internal.Errors
import Development.Shake.Internal.Resource
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Action
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Options
import Development.Shake.Internal.Rules.File
import qualified Data.ByteString as BS
import qualified Data.HashMap.Strict as Map
import General.Extra
import Data.List.Extra
import Data.Hashable
import Data.Typeable
import Data.Dynamic


-- | Get a checksum of a list of files, suitable for using as `shakeVersion`.
--   This will trigger a rebuild when the Shake rules defined in any of the files are changed.
--   For example:
--
-- @
-- main = do
--     ver <- 'getHashedShakeVersion' [\"Shakefile.hs\"]
--     'shakeArgs' 'shakeOptions'{'shakeVersion' = ver} ...
-- @
--
--   To automatically detect the name of the current file, turn on the @TemplateHaskell@
--   extension and write @$(LitE . StringL . loc_filename \<$\> location)@.
--
--   This feature can be turned off during development by passing
--   the flag @--no-rule-version@ or setting 'shakeVersionIgnore' to 'True'.
getHashedShakeVersion :: [FilePath] -> IO String
getHashedShakeVersion :: [FilePath] -> IO FilePath
getHashedShakeVersion [FilePath]
files = do
    [Int]
hashes <- (FilePath -> IO Int) -> [FilePath] -> IO [Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ByteString -> Int) -> IO ByteString -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
0) (IO ByteString -> IO Int)
-> (FilePath -> IO ByteString) -> FilePath -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ByteString
BS.readFile) [FilePath]
files
    FilePath -> IO FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"hash-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> [Int] -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
0 [Int]
hashes)


-- | Get an item from 'shakeExtra', using the requested type as the key. Fails
-- if the value found at this key does not match the requested type.
getShakeExtra :: Typeable a => Action (Maybe a)
getShakeExtra :: Action (Maybe a)
getShakeExtra = IO (Maybe a) -> Action (Maybe a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe a) -> Action (Maybe a))
-> (ShakeOptions -> IO (Maybe a))
-> ShakeOptions
-> Action (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap TypeRep Dynamic -> IO (Maybe a)
forall a. Typeable a => HashMap TypeRep Dynamic -> IO (Maybe a)
lookupShakeExtra (HashMap TypeRep Dynamic -> IO (Maybe a))
-> (ShakeOptions -> HashMap TypeRep Dynamic)
-> ShakeOptions
-> IO (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShakeOptions -> HashMap TypeRep Dynamic
shakeExtra (ShakeOptions -> Action (Maybe a))
-> Action ShakeOptions -> Action (Maybe a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Action ShakeOptions
getShakeOptions

-- | A version of 'getShakeExtra' in 'Rules'.
getShakeExtraRules :: Typeable a => Rules (Maybe a)
getShakeExtraRules :: Rules (Maybe a)
getShakeExtraRules = IO (Maybe a) -> Rules (Maybe a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe a) -> Rules (Maybe a))
-> (ShakeOptions -> IO (Maybe a))
-> ShakeOptions
-> Rules (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap TypeRep Dynamic -> IO (Maybe a)
forall a. Typeable a => HashMap TypeRep Dynamic -> IO (Maybe a)
lookupShakeExtra (HashMap TypeRep Dynamic -> IO (Maybe a))
-> (ShakeOptions -> HashMap TypeRep Dynamic)
-> ShakeOptions
-> IO (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShakeOptions -> HashMap TypeRep Dynamic
shakeExtra (ShakeOptions -> Rules (Maybe a))
-> Rules ShakeOptions -> Rules (Maybe a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Rules ShakeOptions
getShakeOptionsRules

lookupShakeExtra :: forall a . Typeable a => Map.HashMap TypeRep Dynamic -> IO (Maybe a)
lookupShakeExtra :: HashMap TypeRep Dynamic -> IO (Maybe a)
lookupShakeExtra HashMap TypeRep Dynamic
mp =
    case TypeRep -> HashMap TypeRep Dynamic -> Maybe Dynamic
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup TypeRep
want HashMap TypeRep Dynamic
mp of
        Just Dynamic
dyn
            | Just a
x <- Dynamic -> Maybe a
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic Dynamic
dyn -> Maybe a -> IO (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe a -> IO (Maybe a)) -> Maybe a -> IO (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
x
            | Bool
otherwise -> SomeException -> IO (Maybe a)
forall (m :: * -> *) a. MonadIO m => SomeException -> m a
throwM (SomeException -> IO (Maybe a)) -> SomeException -> IO (Maybe a)
forall a b. (a -> b) -> a -> b
$ FilePath
-> [(FilePath, Maybe FilePath)] -> FilePath -> SomeException
errorStructured
                FilePath
"shakeExtra value is malformed, all keys and values must agree"
                [(FilePath
"Key", FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ TypeRep -> FilePath
forall a. Show a => a -> FilePath
show TypeRep
want)
                ,(FilePath
"Value", FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ TypeRep -> FilePath
forall a. Show a => a -> FilePath
show (TypeRep -> FilePath) -> TypeRep -> FilePath
forall a b. (a -> b) -> a -> b
$ Dynamic -> TypeRep
dynTypeRep Dynamic
dyn)]
                FilePath
"Use addShakeExtra to ensure shakeExtra is well-formed"
        Maybe Dynamic
Nothing -> Maybe a -> IO (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
    where want :: TypeRep
want = Proxy a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)

-- | Add a properly structued value to 'shakeExtra' which can be retrieved with 'getShakeExtra'.
addShakeExtra :: Typeable a => a -> Map.HashMap TypeRep Dynamic -> Map.HashMap TypeRep Dynamic
addShakeExtra :: a -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic
addShakeExtra a
x = TypeRep
-> Dynamic -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
Map.insert (a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf a
x) (a -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn a
x)


-- | @copyFile' old new@ copies the existing file from @old@ to @new@.
--   The @old@ file will be tracked as a dependency.
--   Also creates the new directory if necessary.
copyFile' :: Partial => FilePath -> FilePath -> Action ()
copyFile' :: FilePath -> FilePath -> Action ()
copyFile' FilePath
old FilePath
new = do
    Partial => [FilePath] -> Action ()
[FilePath] -> Action ()
need [FilePath
old]
    FilePath -> Action ()
putVerbose (FilePath -> Action ()) -> FilePath -> Action ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Copying from " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
old FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
new
    IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
        FilePath -> IO ()
createDirectoryRecursive (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDirectory FilePath
new
        FilePath -> IO ()
removeFile_ FilePath
new -- symlink safety
        FilePath -> FilePath -> IO ()
copyFile FilePath
old FilePath
new

-- | @copyFileChanged old new@ copies the existing file from @old@ to @new@, if the contents have changed.
--   The @old@ file will be tracked as a dependency.
--   Also creates the new directory if necessary.
copyFileChanged :: Partial => FilePath -> FilePath -> Action ()
copyFileChanged :: FilePath -> FilePath -> Action ()
copyFileChanged FilePath
old FilePath
new = do
    Partial => [FilePath] -> Action ()
[FilePath] -> Action ()
need [FilePath
old]
    -- in newer versions of the directory package we can use copyFileWithMetadata which (we think) updates
    -- the timestamp as well and thus no need to read the source file twice.
    Action Bool -> Action () -> Action ()
forall (m :: * -> *). Monad m => m Bool -> m () -> m ()
unlessM (IO Bool -> Action Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Action Bool) -> IO Bool -> Action Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
new IO Bool -> IO Bool -> IO Bool
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
&&^ FilePath -> FilePath -> IO Bool
IO.fileEq FilePath
old FilePath
new) (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
        FilePath -> Action ()
putVerbose (FilePath -> Action ()) -> FilePath -> Action ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Copying from " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
old FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
new
        IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
            FilePath -> IO ()
createDirectoryRecursive (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDirectory FilePath
new
            -- copyFile does a lot of clever stuff with permissions etc, so make sure we just reuse it
            FilePath -> IO ()
removeFile_ FilePath
new -- symlink safety
            IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
copyFile FilePath
old FilePath
new


-- | Read a file, after calling 'need'. The argument file will be tracked as a dependency.
readFile' :: Partial => FilePath -> Action String
readFile' :: FilePath -> Action FilePath
readFile' FilePath
x = Partial => [FilePath] -> Action ()
[FilePath] -> Action ()
need [FilePath
x] Action () -> Action FilePath -> Action FilePath
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO FilePath -> Action FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO FilePath
readFile FilePath
x)

-- | Write a file, lifted to the 'Action' monad.
writeFile' :: (MonadIO m, Partial) => FilePath -> String -> m ()
writeFile' :: FilePath -> FilePath -> m ()
writeFile' FilePath
name FilePath
x = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    FilePath -> IO ()
createDirectoryRecursive (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDirectory FilePath
name
    FilePath -> IO ()
removeFile_ FilePath
name -- symlink safety
    FilePath -> FilePath -> IO ()
writeFile FilePath
name FilePath
x


-- | A version of 'readFile'' which also splits the result into lines.
--   The argument file will be tracked as a dependency.
readFileLines :: Partial => FilePath -> Action [String]
readFileLines :: FilePath -> Action [FilePath]
readFileLines = (FilePath -> [FilePath]) -> Action FilePath -> Action [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> [FilePath]
lines (Action FilePath -> Action [FilePath])
-> (FilePath -> Action FilePath) -> FilePath -> Action [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Partial => FilePath -> Action FilePath
FilePath -> Action FilePath
readFile'

-- | A version of 'writeFile'' which writes out a list of lines.
writeFileLines :: (MonadIO m, Partial) => FilePath -> [String] -> m ()
writeFileLines :: FilePath -> [FilePath] -> m ()
writeFileLines FilePath
name = FilePath -> FilePath -> m ()
forall (m :: * -> *).
(MonadIO m, Partial) =>
FilePath -> FilePath -> m ()
writeFile' FilePath
name (FilePath -> m ())
-> ([FilePath] -> FilePath) -> [FilePath] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines


-- | Write a file, but only if the contents would change.
writeFileChanged :: (MonadIO m, Partial) => FilePath -> String -> m ()
writeFileChanged :: FilePath -> FilePath -> m ()
writeFileChanged FilePath
name FilePath
x = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    FilePath -> IO ()
createDirectoryRecursive (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeDirectory FilePath
name
    Bool
b <- FilePath -> IO Bool
doesFileExist FilePath
name
    if Bool -> Bool
not Bool
b then FilePath -> FilePath -> IO ()
writeFile FilePath
name FilePath
x else do
        -- Cannot use ByteString here, since it has different line handling
        -- semantics on Windows
        Bool
b <- FilePath -> IOMode -> (Handle -> IO Bool) -> IO Bool
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
name IOMode
ReadMode ((Handle -> IO Bool) -> IO Bool) -> (Handle -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
            FilePath
src <- Handle -> IO FilePath
hGetContents Handle
h
            Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! FilePath
src FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
x
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            FilePath -> IO ()
removeFile_ FilePath
name -- symlink safety
            FilePath -> FilePath -> IO ()
writeFile FilePath
name FilePath
x


-- | Create a temporary file in the temporary directory. The file will be deleted
--   after the action completes (provided the file is not still open).
--   The 'FilePath' will not have any file extension, will exist, and will be zero bytes long.
--   If you require a file with a specific name, use 'withTempDir'.
withTempFile :: (FilePath -> Action a) -> Action a
withTempFile :: (FilePath -> Action a) -> Action a
withTempFile FilePath -> Action a
act = do
    (FilePath
file, IO ()
del) <- IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (FilePath, IO ())
IO.newTempFile
    FilePath -> Action a
act FilePath
file Action a -> IO () -> Action a
forall a b. Action a -> IO b -> Action a
`actionFinally` IO ()
del

-- | Like 'withTempFile' but using a custom temporary directory.
withTempFileWithin :: FilePath -> (FilePath -> Action a) -> Action a
withTempFileWithin :: FilePath -> (FilePath -> Action a) -> Action a
withTempFileWithin FilePath
tdir FilePath -> Action a
act = do
    (FilePath
file, IO ()
del) <- IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FilePath, IO ()) -> Action (FilePath, IO ()))
-> IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (FilePath, IO ())
IO.newTempFileWithin FilePath
tdir
    FilePath -> Action a
act FilePath
file Action a -> IO () -> Action a
forall a b. Action a -> IO b -> Action a
`actionFinally` IO ()
del


-- | Create a temporary directory inside the system temporary directory.
--   The directory will be deleted after the action completes. As an example:
--
-- @
-- 'withTempDir' $ \\mydir -> do
--    'putInfo' $ \"Temp directory is \" ++ mydir
--    'writeFile'' (mydir \</\> \"test.txt\") \"writing out a temp file\"
-- @
withTempDir :: (FilePath -> Action a) -> Action a
withTempDir :: (FilePath -> Action a) -> Action a
withTempDir FilePath -> Action a
act = do
    (FilePath
dir,IO ()
del) <- IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (FilePath, IO ())
IO.newTempDir
    FilePath -> Action a
act FilePath
dir Action a -> IO () -> Action a
forall a b. Action a -> IO b -> Action a
`actionFinally` IO ()
del

-- | Like 'withTempDir' but using a custom temporary directory.
withTempDirWithin :: FilePath -> (FilePath -> Action a) -> Action a
withTempDirWithin :: FilePath -> (FilePath -> Action a) -> Action a
withTempDirWithin FilePath
tdir FilePath -> Action a
act = do
    (FilePath
dir,IO ()
del) <- IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FilePath, IO ()) -> Action (FilePath, IO ()))
-> IO (FilePath, IO ()) -> Action (FilePath, IO ())
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (FilePath, IO ())
IO.newTempDirWithin FilePath
tdir
    FilePath -> Action a
act FilePath
dir Action a -> IO () -> Action a
forall a b. Action a -> IO b -> Action a
`actionFinally` IO ()
del



-- | A 'parallel' version of 'forM'.
forP :: [a] -> (a -> Action b) -> Action [b]
forP :: [a] -> (a -> Action b) -> Action [b]
forP [a]
xs a -> Action b
f = [Action b] -> Action [b]
forall a. [Action a] -> Action [a]
parallel ([Action b] -> Action [b]) -> [Action b] -> Action [b]
forall a b. (a -> b) -> a -> b
$ (a -> Action b) -> [a] -> [Action b]
forall a b. (a -> b) -> [a] -> [b]
map a -> Action b
f [a]
xs

-- | Execute two operations in parallel, based on 'parallel'.
par :: Action a -> Action b -> Action (a,b)
par :: Action a -> Action b -> Action (a, b)
par Action a
a Action b
b = (\[Left a
a, Right b
b] -> (a
a,b
b)) ([Either a b] -> (a, b)) -> Action [Either a b] -> Action (a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Action (Either a b)] -> Action [Either a b]
forall a. [Action a] -> Action [a]
parallel [a -> Either a b
forall a b. a -> Either a b
Left (a -> Either a b) -> Action a -> Action (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Action a
a, b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> Action b -> Action (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Action b
b]


-- | Create a finite resource, given a name (for error messages) and a quantity of the resource that exists.
--   Shake will ensure that actions using the same finite resource do not execute in parallel.
--   As an example, only one set of calls to the Excel API can occur at one time, therefore
--   Excel is a finite resource of quantity 1. You can write:
--
-- @
-- 'Development.Shake.shake' 'Development.Shake.shakeOptions'{'Development.Shake.shakeThreads'=2} $ do
--    'Development.Shake.want' [\"a.xls\",\"b.xls\"]
--    excel <- 'Development.Shake.newResource' \"Excel\" 1
--    \"*.xls\" 'Development.Shake.%>' \\out ->
--        'Development.Shake.withResource' excel 1 $
--            'Development.Shake.cmd' \"excel\" out ...
-- @
--
--   Now the two calls to @excel@ will not happen in parallel.
--
--   As another example, calls to compilers are usually CPU bound but calls to linkers are usually
--   disk bound. Running 8 linkers will often cause an 8 CPU system to grid to a halt. We can limit
--   ourselves to 4 linkers with:
--
-- @
-- disk <- 'Development.Shake.newResource' \"Disk\" 4
-- 'Development.Shake.want' [show i 'Development.Shake.FilePath.<.>' \"exe\" | i <- [1..100]]
-- \"*.exe\" 'Development.Shake.%>' \\out ->
--     'Development.Shake.withResource' disk 1 $
--         'Development.Shake.cmd' \"ld -o\" [out] ...
-- \"*.o\" 'Development.Shake.%>' \\out ->
--     'Development.Shake.cmd' \"cl -o\" [out] ...
-- @
newResource :: String -> Int -> Rules Resource
newResource :: FilePath -> Int -> Rules Resource
newResource FilePath
name Int
mx = IO Resource -> Rules Resource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> Rules Resource) -> IO Resource -> Rules Resource
forall a b. (a -> b) -> a -> b
$ FilePath -> Int -> IO Resource
newResourceIO FilePath
name Int
mx


-- | Create a throttled resource, given a name (for error messages) and a number of resources (the 'Int') that can be
--   used per time period (the 'Double' in seconds). Shake will ensure that actions using the same throttled resource
--   do not exceed the limits. As an example, let us assume that making more than 1 request every 5 seconds to
--   Google results in our client being blacklisted, we can write:
--
-- @
-- google <- 'Development.Shake.newThrottle' \"Google\" 1 5
-- \"*.url\" 'Development.Shake.%>' \\out -> do
--     'Development.Shake.withResource' google 1 $
--         'Development.Shake.cmd' \"wget\" [\"https:\/\/google.com?q=\" ++ 'Development.Shake.FilePath.takeBaseName' out] \"-O\" [out]
-- @
--
--   Now we will wait at least 5 seconds after querying Google before performing another query. If Google change the rules to
--   allow 12 requests per minute we can instead use @'Development.Shake.newThrottle' \"Google\" 12 60@, which would allow
--   greater parallelisation, and avoid throttling entirely if only a small number of requests are necessary.
--
--   In the original example we never make a fresh request until 5 seconds after the previous request has /completed/. If we instead
--   want to throttle requests since the previous request /started/ we can write:
--
-- @
-- google <- 'Development.Shake.newThrottle' \"Google\" 1 5
-- \"*.url\" 'Development.Shake.%>' \\out -> do
--     'Development.Shake.withResource' google 1 $ pure ()
--     'Development.Shake.cmd' \"wget\" [\"https:\/\/google.com?q=\" ++ 'Development.Shake.FilePath.takeBaseName' out] \"-O\" [out]
-- @
--
--   However, the rule may not continue running immediately after 'Development.Shake.withResource' completes, so while
--   we will never exceed an average of 1 request every 5 seconds, we may end up running an unbounded number of
--   requests simultaneously. If this limitation causes a problem in practice it can be fixed.
newThrottle :: String -> Int -> Double -> Rules Resource
newThrottle :: FilePath -> Int -> Double -> Rules Resource
newThrottle FilePath
name Int
count Double
period = IO Resource -> Rules Resource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> Rules Resource) -> IO Resource -> Rules Resource
forall a b. (a -> b) -> a -> b
$ FilePath -> Int -> Double -> IO Resource
newThrottleIO FilePath
name Int
count Double
period


-- | Run an action which uses part of several finite resources. Acquires the resources in a stable
--   order, to prevent deadlock. If all rules requiring more than one resource acquire those
--   resources with a single call to 'withResources', resources will not deadlock.
withResources :: [(Resource, Int)] -> Action a -> Action a
withResources :: [(Resource, Int)] -> Action a -> Action a
withResources [(Resource, Int)]
res Action a
act
    | (Resource
r,Int
i):[(Resource, Int)]
_ <- ((Resource, Int) -> Bool) -> [(Resource, Int)] -> [(Resource, Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Int -> Bool)
-> ((Resource, Int) -> Int) -> (Resource, Int) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Resource, Int) -> Int
forall a b. (a, b) -> b
snd) [(Resource, Int)]
res = FilePath -> Action a
forall a. Partial => FilePath -> a
error (FilePath -> Action a) -> FilePath -> Action a
forall a b. (a -> b) -> a -> b
$ FilePath
"You cannot acquire a negative quantity of " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Resource -> FilePath
forall a. Show a => a -> FilePath
show Resource
r FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
", requested " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
i
    | Bool
otherwise = [(Resource, [Int])] -> Action a
forall (t :: * -> *). Foldable t => [(Resource, t Int)] -> Action a
f ([(Resource, [Int])] -> Action a)
-> [(Resource, [Int])] -> Action a
forall a b. (a -> b) -> a -> b
$ [(Resource, Int)] -> [(Resource, [Int])]
forall k v. Ord k => [(k, v)] -> [(k, [v])]
groupSort [(Resource, Int)]
res
    where
        f :: [(Resource, t Int)] -> Action a
f [] = Action a
act
        f ((Resource
r,t Int
xs):[(Resource, t Int)]
rs) = Resource -> Int -> Action a -> Action a
forall a. Resource -> Int -> Action a -> Action a
withResource Resource
r (t Int -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum t Int
xs) (Action a -> Action a) -> Action a -> Action a
forall a b. (a -> b) -> a -> b
$ [(Resource, t Int)] -> Action a
f [(Resource, t Int)]
rs


-- | Given an action on a key, produce a cached version that will execute the action at most once per key per run.
--   Using the cached result will still result include any dependencies that the action requires - e.g. if the action
--   does 'need' then those dependencies will be added to every rule that uses that cache.
--   Each call to 'newCache' creates a separate cache that is independent of all other calls to 'newCache'.
--
--   The operations will not be cached between runs and nothing will be persisted to the Shake database.
--   For an alternative that does persist the cache, see 'Development.Shake.addOracleCache'.
--
--   This function is useful when creating files that store intermediate values,
--   to avoid the overhead of repeatedly reading from disk, particularly if the file requires expensive parsing.
--   As an example:
--
-- @
-- digits \<- 'newCache' $ \\file -> do
--     src \<- readFile\' file
--     pure $ length $ filter isDigit src
-- \"*.digits\" 'Development.Shake.%>' \\x -> do
--     v1 \<- digits ('dropExtension' x)
--     v2 \<- digits ('dropExtension' x)
--     'Development.Shake.writeFile'' x $ show (v1,v2)
-- @
--
--   To create the result @MyFile.txt.digits@ the file @MyFile.txt@ will be read and counted, but only at most
--   once per execution.
newCache :: (Eq k, Hashable k) => (k -> Action v) -> Rules (k -> Action v)
newCache :: (k -> Action v) -> Rules (k -> Action v)
newCache = IO (k -> Action v) -> Rules (k -> Action v)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (k -> Action v) -> Rules (k -> Action v))
-> ((k -> Action v) -> IO (k -> Action v))
-> (k -> Action v)
-> Rules (k -> Action v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> Action v) -> IO (k -> Action v)
forall k v.
(Eq k, Hashable k) =>
(k -> Action v) -> IO (k -> Action v)
newCacheIO