{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
module SysTools.BaseDir
( expandTopDir, expandToolDir
, findTopDir, findToolDir
) where
#include "HsVersions.h"
import GhcPrelude
import Panic
import System.Environment (lookupEnv)
import System.FilePath
import Data.List
#if defined(darwin_HOST_OS) || defined(linux_HOST_OS) || defined(freebsd_HOST_OS)
import System.Environment (getExecutablePath)
#endif
#if defined(mingw32_HOST_OS)
import System.Environment (getExecutablePath)
import System.Directory (doesDirectoryExist)
#endif
#if defined(mingw32_HOST_OS)
# if defined(i386_HOST_ARCH)
# define WINDOWS_CCONV stdcall
# elif defined(x86_64_HOST_ARCH)
# define WINDOWS_CCONV ccall
# else
# error Unknown mingw32 arch
# endif
#endif
expandTopDir :: FilePath -> String -> String
expandTopDir :: FilePath -> FilePath -> FilePath
expandTopDir = FilePath -> FilePath -> FilePath -> FilePath
expandPathVar "topdir"
expandToolDir :: Maybe FilePath -> String -> String
#if defined(mingw32_HOST_OS)
expandToolDir (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
expandToolDir Nothing _ = panic "Could not determine $tooldir"
#else
expandToolDir :: Maybe FilePath -> FilePath -> FilePath
expandToolDir _ s :: FilePath
s = FilePath
s
#endif
expandPathVar :: String -> FilePath -> String -> String
expandPathVar :: FilePath -> FilePath -> FilePath -> FilePath
expandPathVar var :: FilePath
var value :: FilePath
value str :: FilePath
str
| Just str' :: FilePath
str' <- FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix ('$'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
var) FilePath
str
, FilePath -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
str' Bool -> Bool -> Bool
|| Char -> Bool
isPathSeparator (FilePath -> Char
forall a. [a] -> a
head FilePath
str')
= FilePath
value FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
var FilePath
value FilePath
str'
expandPathVar var :: FilePath
var value :: FilePath
value (x :: Char
x:xs :: FilePath
xs) = Char
x Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
var FilePath
value FilePath
xs
expandPathVar _ _ [] = []
findTopDir :: Maybe String
-> IO String
findTopDir :: Maybe FilePath -> IO FilePath
findTopDir (Just minusb :: FilePath
minusb) = FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> FilePath
normalise FilePath
minusb)
findTopDir Nothing
= do
Maybe FilePath
maybe_env_top_dir <- FilePath -> IO (Maybe FilePath)
lookupEnv "_GHC_TOP_DIR"
case Maybe FilePath
maybe_env_top_dir of
Just env_top_dir :: FilePath
env_top_dir -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
env_top_dir
Nothing -> do
Maybe FilePath
maybe_exec_dir <- IO (Maybe FilePath)
getBaseDir
case Maybe FilePath
maybe_exec_dir of
Nothing -> GhcException -> IO FilePath
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO FilePath) -> GhcException -> IO FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> GhcException
InstallationError "missing -B<dir> option"
Just dir :: FilePath
dir -> FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
dir
getBaseDir :: IO (Maybe String)
#if defined(mingw32_HOST_OS)
rootDir :: FilePath -> FilePath
rootDir = takeDirectory . takeDirectory . normalise
getBaseDir = Just . (\p -> p </> "lib") . rootDir <$> getExecutablePath
#elif defined(darwin_HOST_OS) || defined(linux_HOST_OS) || defined(freebsd_HOST_OS)
getBaseDir :: IO (Maybe FilePath)
getBaseDir = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath)
-> (FilePath -> FilePath) -> FilePath -> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\p :: FilePath
p -> FilePath
p FilePath -> FilePath -> FilePath
</> "lib") (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDirectory (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDirectory (FilePath -> Maybe FilePath) -> IO FilePath -> IO (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getExecutablePath
#else
getBaseDir = return Nothing
#endif
findToolDir
:: FilePath
-> IO (Maybe FilePath)
#if defined(mingw32_HOST_OS)
findToolDir top_dir = go 0 (top_dir </> "..")
where maxDepth = 3
go :: Int -> FilePath -> IO (Maybe FilePath)
go k path
| k == maxDepth = throwGhcExceptionIO $
InstallationError "could not detect mingw toolchain"
| otherwise = do
oneLevel <- doesDirectoryExist (path </> "mingw")
if oneLevel
then return (Just path)
else go (k+1) (path </> "..")
#else
findToolDir :: FilePath -> IO (Maybe FilePath)
findToolDir _ = Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
#endif