{-# LANGUAGE CPP #-}
module GHC.BaseDir
  ( expandTopDir
  , expandPathVar
  , getBaseDir
  ) where
import Prelude 
import Data.List (stripPrefix)
import Data.Maybe (listToMaybe)
import System.FilePath
#if MIN_VERSION_base(4,17,0) && !defined(openbsd_HOST_OS)
import System.Environment (executablePath)
#else
import System.Environment (getExecutablePath)
#endif
expandTopDir :: FilePath -> String -> String
expandTopDir :: FilePath -> FilePath -> FilePath
expandTopDir = FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
"topdir"
expandPathVar :: String -> FilePath -> String -> String
expandPathVar :: FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
var FilePath
value FilePath
str
  | Just FilePath
str' <- FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix (Char
'$'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
var) FilePath
str
  , Bool -> (Char -> Bool) -> Maybe Char -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True Char -> Bool
isPathSeparator (FilePath -> Maybe Char
forall a. [a] -> Maybe a
listToMaybe FilePath
str')
  = FilePath
value FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
var FilePath
value FilePath
str'
expandPathVar FilePath
var FilePath
value (Char
x:FilePath
xs) = Char
x Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath -> FilePath -> FilePath -> FilePath
expandPathVar FilePath
var FilePath
value FilePath
xs
expandPathVar FilePath
_ FilePath
_ [] = []
#if !MIN_VERSION_base(4,17,0) || defined(openbsd_HOST_OS)
executablePath :: Maybe (IO (Maybe FilePath))
executablePath = Just (Just <$> getExecutablePath)
#elif !MIN_VERSION_base(4,18,0) && defined(js_HOST_ARCH)
executablePath :: Maybe (IO (Maybe FilePath))
executablePath = Nothing
#endif
getBaseDir :: IO (Maybe String)
#if defined(mingw32_HOST_OS)
getBaseDir = maybe (pure Nothing) ((((</> "lib") . rootDir) <$>) <$>) executablePath
  where
    
    
    
    rootDir :: FilePath -> FilePath
    rootDir = takeDirectory . takeDirectory . normalise
#else
getBaseDir :: IO (Maybe FilePath)
getBaseDir = IO (Maybe FilePath)
-> (IO (Maybe FilePath) -> IO (Maybe FilePath))
-> Maybe (IO (Maybe FilePath))
-> IO (Maybe FilePath)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe FilePath -> IO (Maybe FilePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FilePath
forall a. Maybe a
Nothing) ((((FilePath -> FilePath -> FilePath
</> FilePath
"lib") (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
rootDir) (FilePath -> FilePath) -> Maybe FilePath -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Maybe FilePath -> Maybe FilePath)
-> IO (Maybe FilePath) -> IO (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) Maybe (IO (Maybe FilePath))
executablePath
  where
    rootDir :: FilePath -> FilePath
    rootDir :: FilePath -> FilePath
rootDir = FilePath -> FilePath
takeDirectory (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDirectory
#endif