never executed always true always false
    1 {-# LANGUAGE CPP #-}
    2 {-# LANGUAGE ScopedTypeVariables #-}
    3 
    4 {-
    5 -----------------------------------------------------------------------------
    6 --
    7 -- (c) The University of Glasgow 2001-2017
    8 --
    9 -- Finding the compiler's base directory.
   10 --
   11 -----------------------------------------------------------------------------
   12 -}
   13 
   14 module GHC.SysTools.BaseDir
   15   ( expandTopDir, expandToolDir
   16   , findTopDir, findToolDir
   17   , tryFindTopDir
   18   ) where
   19 
   20 import GHC.Prelude
   21 
   22 -- See note [Base Dir] for why some of this logic is shared with ghc-pkg.
   23 import GHC.BaseDir
   24 
   25 import GHC.Utils.Panic
   26 
   27 import System.Environment (lookupEnv)
   28 import System.FilePath
   29 
   30 -- Windows
   31 #if defined(mingw32_HOST_OS)
   32 import System.Directory (doesDirectoryExist)
   33 #endif
   34 
   35 {-
   36 Note [topdir: How GHC finds its files]
   37 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
   38 
   39 GHC needs various support files (library packages, RTS etc), plus
   40 various auxiliary programs (cp, gcc, etc).  It starts by finding topdir,
   41 the root of GHC's support files
   42 
   43 On Unix:
   44   - ghc always has a shell wrapper that passes a -B<dir> option
   45 
   46 On Windows:
   47   - ghc never has a shell wrapper.
   48   - we can find the location of the ghc binary, which is
   49         $topdir/<foo>/<something>.exe
   50     where <something> may be "ghc", "ghc-stage2", or similar
   51   - we strip off the "<foo>/<something>.exe" to leave $topdir.
   52 
   53 from topdir we can find package.conf, ghc-asm, etc.
   54 
   55 
   56 Note [tooldir: How GHC finds mingw on Windows]
   57 
   58 GHC has some custom logic on Windows for finding the mingw
   59 toolchain and perl. Depending on whether GHC is built
   60 with the make build system or Hadrian, and on whether we're
   61 running a bindist, we might find the mingw toolchain
   62 either under $topdir/../{mingw, perl}/ or
   63 $topdir/../../{mingw, perl}/.
   64 
   65 This story is long and with lots of twist and turns..  But lets talk about how
   66 the build system finds and wires through the toolchain information.
   67 
   68 1) It all starts in configure.ac which has two modes it operates on:
   69    a) The default is where `EnableDistroToolchain` is false.  This indicates
   70       that we want to use the in-tree bundled toolchains.  In this mode we will
   71       download and unpack some custom toolchains into the `inplace/mingw` folder
   72       and everything is pointed to that folder.
   73    b) The second path is when `EnableDistroToolchain` is true.  This makes the
   74       toolchain behave a lot like Linux, in that  the environment is queried for
   75       information on the tools we require.
   76 
   77   From configure.ac we export the standard variables to set the paths to the
   78   tools for the build system to use.
   79 
   80 2) After we have the path to the tools we have to generate the right paths to
   81    store in the settings file for ghc to use.  This is done in aclocal.m4.
   82    Again we have two modes of operation:
   83    a) If not `EnableDistroToolchain` the paths are rewritten to paths using a
   84       variable `$tooldir` as we need an absolute path.  $tooldir is filled in by
   85       the `expandToolDir` function in this module at GHC startup.
   86    b) When `EnableDistroToolchain` then instead of filling in a absolute path
   87       we fill in just the program name.  The assumption here is that at runtime
   88       the environment GHC is operating on will be the same as the one configure
   89       was run in.  This means we expect `gcc, ld, as` etc to be on the PATH.
   90 
   91   From `aclocal.m4` we export a couple of variables starting with `Settings`
   92   which will be used to generate the settings file.
   93 
   94 3) The next step is to generate the settings file, this is where things diverge
   95    based on the build system.  Both Make and Hadrian handle this differently:
   96 
   97 make)
   98   Make deals with this rather simply.  As an output of configure.ac
   99   `config.mk.in` is processed and `config.mk` generated which has the values we
  100   set in `aclocal.m4`. This allows the rest of the build system to have access
  101   to these and other values determined by configure.
  102 
  103   Based on this file, `rts/include/ghc.mk` when ran will produce the settings file
  104   by echoing the values into a the final file.  Coincidentally this is also
  105   where `ghcplatform.h` and `ghcversion.h` generated which contains information
  106   about the build platform and sets CPP for use by the entire build.
  107 
  108 hadrian)
  109   For hadrian the file `cfg/system.config.in` is preprocessed by configure and
  110   the output written to `system.config`.  This serves the same purpose as
  111   `config.mk` but it rewrites the values that were exported.  As an example
  112   `SettingsCCompilerCommand` is rewritten to `settings-c-compiler-command`.
  113 
  114   Next up is `src/Oracles/Settings.hs` which makes from some Haskell ADT to
  115   the settings `keys` in the `system.config`.  As an example,
  116   `settings-c-compiler-command` is mapped to
  117   `SettingsFileSetting_CCompilerCommand`.
  118 
  119   The last part of this is the `generateSettings` in `src/Rules/Generate.hs`
  120   which produces the desired settings file out of Hadrian. This is the
  121   equivalent to `rts/include/ghc.mk`.
  122 
  123 --
  124 
  125 So why do we have these? On Windows there's no such thing as a platform compiler
  126 and as such we need to provide GCC and binutils.  The easiest way is to bundle
  127 these with the compiler and wire them up.  This gives you a relocatable
  128 binball.  This works fine for most users.  However mingw-w64 have a different
  129 requirement.  They require all packages in the repo to be compiled using the
  130 same version of the compiler.  So it means when they are rebuilding the world to
  131 add support for GCC X, they expect all packages to have been compiled with GCC X
  132 which is a problem since we ship an older GCC version.
  133 
  134 GHC is a package in mingw-w64 because there are Haskell packages in the
  135 repository which of course requires a Haskell compiler.  To help them we
  136 provide the override which allows GHC to instead of using an inplace compiler to
  137 play nice with the system compiler instead.
  138 -}
  139 
  140 -- | Expand occurrences of the @$tooldir@ interpolation in a string
  141 -- on Windows, leave the string untouched otherwise.
  142 expandToolDir :: Maybe FilePath -> String -> String
  143 #if defined(mingw32_HOST_OS) && !defined(USE_INPLACE_MINGW_TOOLCHAIN)
  144 expandToolDir (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
  145 expandToolDir Nothing         _ = panic "Could not determine $tooldir"
  146 #else
  147 expandToolDir _ s = s
  148 #endif
  149 
  150 -- | Returns a Unix-format path pointing to TopDir.
  151 findTopDir :: Maybe String -- Maybe TopDir path (without the '-B' prefix).
  152            -> IO String    -- TopDir (in Unix format '/' separated)
  153 findTopDir m_minusb = do
  154   maybe_exec_dir <- tryFindTopDir m_minusb
  155   case maybe_exec_dir of
  156       -- "Just" on Windows, "Nothing" on unix
  157       Nothing -> throwGhcExceptionIO $
  158           InstallationError "missing -B<dir> option"
  159       Just dir -> return dir
  160 
  161 tryFindTopDir
  162   :: Maybe String -- ^ Maybe TopDir path (without the '-B' prefix).
  163   -> IO (Maybe String) -- ^ TopDir (in Unix format '/' separated)
  164 tryFindTopDir (Just minusb) = return $ Just $ normalise minusb
  165 tryFindTopDir Nothing
  166     = do -- The _GHC_TOP_DIR environment variable can be used to specify
  167          -- the top dir when the -B argument is not specified. It is not
  168          -- intended for use by users, it was added specifically for the
  169          -- purpose of running GHC within GHCi.
  170          maybe_env_top_dir <- lookupEnv "_GHC_TOP_DIR"
  171          case maybe_env_top_dir of
  172              Just env_top_dir -> return $ Just env_top_dir
  173              -- Try directory of executable
  174              Nothing -> getBaseDir
  175 
  176 
  177 -- See Note [tooldir: How GHC finds mingw on Windows]
  178 -- Returns @Nothing@ when not on Windows.
  179 -- When called on Windows, it either throws an error when the
  180 -- tooldir can't be located, or returns @Just tooldirpath@.
  181 -- If the distro toolchain is being used we treat Windows the same as Linux
  182 findToolDir
  183   :: FilePath -- ^ topdir
  184   -> IO (Maybe FilePath)
  185 #if defined(mingw32_HOST_OS) && !defined(USE_INPLACE_MINGW_TOOLCHAIN)
  186 findToolDir top_dir = go 0 (top_dir </> "..") []
  187   where maxDepth = 3
  188         go :: Int -> FilePath -> [FilePath] -> IO (Maybe FilePath)
  189         go k path tried
  190           | k == maxDepth = throwGhcExceptionIO $
  191               InstallationError $ "could not detect mingw toolchain in the following paths: " ++ show tried
  192           | otherwise = do
  193               let try = path </> "mingw"
  194               let tried = tried ++ [try]
  195               oneLevel <- doesDirectoryExist try
  196               if oneLevel
  197                 then return (Just path)
  198                 else go (k+1) (path </> "..") tried
  199 #else
  200 findToolDir _ = return Nothing
  201 #endif