module Development.Shake.Internal.Derived(
    copyFile', copyFileChanged,
    readFile', readFileLines,
    writeFile', writeFileLines, writeFileChanged,
    withTempFile, withTempDir,
    getHashedShakeVersion,
    getShakeExtra, addShakeExtra,
    apply1,
    par, forP
    ) where
import Control.Applicative
import Control.Monad.Extra
import Control.Monad.IO.Class
import System.Directory
import General.Extra
import System.FilePath (takeDirectory)
import System.IO.Extra hiding (withTempFile, withTempDir, readFile')
import Development.Shake.Internal.Core.Run
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 Data.Hashable
import Data.Typeable.Extra
import Data.Dynamic
import Prelude
getHashedShakeVersion :: [FilePath] -> IO String
getHashedShakeVersion files = do
    hashes <- mapM (fmap (hashWithSalt 0) . BS.readFile) files
    return $ "hash-" ++ show (hashWithSalt 0 hashes)
getShakeExtra :: Typeable a => Action (Maybe a)
getShakeExtra = withResultType $ \(_ :: Maybe (Action (Maybe a))) -> do
    let want = typeRep (Proxy :: Proxy a)
    extra <- shakeExtra <$> getShakeOptions
    case Map.lookup want extra of
        Just dyn
            | Just x <- fromDynamic dyn -> return $ Just x
            | otherwise -> fail $
                "getShakeExtra: Key " ++ show want ++ " had value of unexpected type " ++ show (dynTypeRep dyn)
        Nothing -> return Nothing
addShakeExtra :: Typeable a => a -> Map.HashMap TypeRep Dynamic -> Map.HashMap TypeRep Dynamic
addShakeExtra x = Map.insert (typeOf x) (toDyn x)
copyFile' :: FilePath -> FilePath -> Action ()
copyFile' old new = do
    need [old]
    putLoud $ "Copying from " ++ old ++ " to " ++ new
    liftIO $ createDirectoryIfMissing True $ takeDirectory new
    liftIO $ copyFile old new
copyFileChanged :: FilePath -> FilePath -> Action ()
copyFileChanged old new = do
    need [old]
    
    
    unlessM (liftIO $ doesFileExist new &&^ fileEq old new) $ do
        putLoud $ "Copying from " ++ old ++ " to " ++ new
        liftIO $ createDirectoryIfMissing True $ takeDirectory new
        
        liftIO $ copyFile old new
readFile' :: FilePath -> Action String
readFile' x = need [x] >> liftIO (readFile x)
writeFile' :: MonadIO m => FilePath -> String -> m ()
writeFile' name x = liftIO $ writeFile name x
readFileLines :: FilePath -> Action [String]
readFileLines = fmap lines . readFile'
writeFileLines :: MonadIO m => FilePath -> [String] -> m ()
writeFileLines name = writeFile' name . unlines
writeFileChanged :: MonadIO m => FilePath -> String -> m ()
writeFileChanged name x = liftIO $ do
    b <- doesFileExist name
    if not b then writeFile name x else do
        
        
        b <- withFile name ReadMode $ \h -> do
            src <- hGetContents h
            return $! src /= x
        when b $ writeFile name x
withTempFile :: (FilePath -> Action a) -> Action a
withTempFile act = do
    (file, del) <- liftIO newTempFile
    act file `actionFinally` del
withTempDir :: (FilePath -> Action a) -> Action a
withTempDir act = do
    (dir,del) <- liftIO newTempDir
    act dir `actionFinally` del
forP :: [a] -> (a -> Action b) -> Action [b]
forP xs f = parallel $ map f xs
par :: Action a -> Action b -> Action (a,b)
par a b = do [Left a, Right b] <- parallel [Left <$> a, Right <$> b]; return (a,b)