{-# LANGUAGE CPP #-}

#ifdef FILE_EMBED
{-# LANGUAGE TemplateHaskell #-}
#endif

-- | The information from Paths_shake cleaned up
module Development.Shake.Internal.Paths(
    shakeVersionString,
    initDataDirectory,
    hasManualData, copyManualData,
    readDataFileHTML
    ) where

import Control.Monad.Extra
import Data.Version
import System.FilePath
import General.Extra
import qualified Data.ByteString.Lazy as LBS
import Paths_shake

#ifdef FILE_EMBED
import qualified Data.ByteString as BS
import Data.FileEmbed
#else
import Control.Exception
import System.Directory
import System.Info.Extra
import System.IO.Unsafe
import System.Environment
#endif

shakeVersionString :: String
shakeVersionString :: FilePath
shakeVersionString = Version -> FilePath
showVersion Version
version

#ifdef FILE_EMBED

initDataDirectory :: IO ()
initDataDirectory = pure ()

htmlDataFiles :: [(FilePath, BS.ByteString)]
htmlDataFiles =
  [ ("profile.html",  $(embedFile "html/profile.html"))
  , ("progress.html", $(embedFile "html/progress.html"))
  , ("shake.js",      $(embedFile "html/shake.js"))
  ]

readDataFileHTML :: FilePath -> IO LBS.ByteString
readDataFileHTML file = do
    case lookup file htmlDataFiles of
      Nothing -> fail $ "Could not find data file " ++ file ++ " in embedded data files!"
      Just x  -> pure (LBS.fromStrict x)

manualDirData :: [(FilePath, BS.ByteString)]
manualDirData = $(embedDir "docs/manual")

hasManualData :: IO Bool
hasManualData = pure True

copyManualData :: FilePath -> IO ()
copyManualData dest = do
    createDirectoryRecursive dest
    forM_ manualDirData $ \(file, bs) -> do
        BS.writeFile (dest </> file) bs

#else
-- We want getDataFileName to be relative to the current directory on program startup,
-- even if we issue a change directory command. Therefore, first call caches, future ones read.
{-# NOINLINE dataDirs #-}
dataDirs :: [String]
dataDirs :: [FilePath]
dataDirs = IO [FilePath] -> [FilePath]
forall a. IO a -> a
unsafePerformIO (IO [FilePath] -> [FilePath]) -> IO [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ do
    FilePath
datdir <- IO FilePath
getDataDir
    FilePath
exedir <- FilePath -> FilePath
takeDirectory (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getExecutablePath IO FilePath -> (IOException -> IO FilePath) -> IO FilePath
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
_ -> FilePath -> IO FilePath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
""
    FilePath
curdir <- IO FilePath
getCurrentDirectory
    [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ [FilePath
datdir] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
exedir | FilePath
exedir FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
""] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
curdir]

-- The data files may be located relative to the current directory, if so cache it in advance
initDataDirectory :: IO ()
initDataDirectory :: IO ()
initDataDirectory = IO [FilePath] -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO [FilePath] -> IO ()) -> IO [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> IO [FilePath]
forall a. a -> IO a
evaluate [FilePath]
dataDirs

getDataFile :: FilePath -> IO FilePath
getDataFile :: FilePath -> IO FilePath
getDataFile FilePath
file = do
    let poss :: [FilePath]
poss = (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath
</> FilePath
file) [FilePath]
dataDirs
    [FilePath]
res <- (FilePath -> IO Bool) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM FilePath -> IO Bool
doesFileExist_ [FilePath]
poss
    case [FilePath]
res of
        [] -> FilePath -> IO FilePath
forall a. FilePath -> IO a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath
"Could not find data file " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
", looked in:") FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) [FilePath]
poss
        FilePath
x:[FilePath]
_ -> FilePath -> IO FilePath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
x

hasDataFile :: FilePath -> IO Bool
hasDataFile :: FilePath -> IO Bool
hasDataFile FilePath
file = (FilePath -> IO Bool) -> [FilePath] -> IO Bool
forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
anyM (\FilePath
dir -> FilePath -> IO Bool
doesFileExist_ (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
file) [FilePath]
dataDirs

readDataFileHTML :: FilePath -> IO LBS.ByteString
readDataFileHTML :: FilePath -> IO ByteString
readDataFileHTML FilePath
file = FilePath -> IO ByteString
LBS.readFile (FilePath -> IO ByteString) -> IO FilePath -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FilePath -> IO FilePath
getDataFile (FilePath
"html" FilePath -> FilePath -> FilePath
</> FilePath
file)

manualFiles :: [FilePath]
manualFiles :: [FilePath]
manualFiles = (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"docs/manual" FilePath -> FilePath -> FilePath
</>) [FilePath
"Shakefile.hs",FilePath
"main.c",FilePath
"constants.c",FilePath
"constants.h",FilePath
"build" FilePath -> FilePath -> FilePath
<.> if Bool
isWindows then FilePath
"bat" else FilePath
"sh"]

hasManualData :: IO Bool
hasManualData :: IO Bool
hasManualData = (FilePath -> IO Bool) -> [FilePath] -> IO Bool
forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
allM FilePath -> IO Bool
hasDataFile [FilePath]
manualFiles

copyManualData :: FilePath -> IO ()
copyManualData :: FilePath -> IO ()
copyManualData FilePath
dest = do
    FilePath -> IO ()
createDirectoryRecursive FilePath
dest
    [FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [FilePath]
manualFiles ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
file -> do
        FilePath
src <- FilePath -> IO FilePath
getDataFile FilePath
file
        FilePath -> FilePath -> IO ()
copyFile FilePath
src (FilePath
dest FilePath -> FilePath -> FilePath
</> FilePath -> FilePath
takeFileName FilePath
file)
#endif