{- ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow 2001-2003 -- -- Access to system tools: gcc, cp, rm etc -- ----------------------------------------------------------------------------- -} {-# LANGUAGE CPP, ScopedTypeVariables #-} module SysTools ( -- Initialisation initSysTools, -- Interface to system tools runUnlit, runCpp, runCc, -- [Option] -> IO () runPp, -- [Option] -> IO () runSplit, -- [Option] -> IO () runAs, runLink, runLibtool, -- [Option] -> IO () runMkDLL, runWindres, runLlvmOpt, runLlvmLlc, runClang, figureLlvmVersion, getLinkerInfo, getCompilerInfo, linkDynLib, askLd, touch, -- String -> String -> IO () copy, copyWithHeader, -- Temporary-file management setTmpDir, newTempName, newTempLibName, cleanTempDirs, cleanTempFiles, cleanTempFilesExcept, addFilesToClean, Option(..), -- frameworks getPkgFrameworkOpts, getFrameworkOpts ) where #include "HsVersions.h" import DriverPhases import Module import Packages import Config import Outputable import ErrUtils import Panic import Platform import Util import DynFlags import Exception import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion) import Data.IORef import Control.Monad import System.Exit import System.Environment import System.FilePath import System.IO import System.IO.Error as IO import System.Directory import Data.Char import Data.List import qualified Data.Map as Map import qualified Data.Set as Set #ifndef mingw32_HOST_OS import qualified System.Posix.Internals #else /* Must be Win32 */ import Foreign import Foreign.C.String #if MIN_VERSION_Win32(2,5,0) import qualified System.Win32.Types as Win32 #else import qualified System.Win32.Info as Win32 #endif import System.Win32.Types (DWORD, LPTSTR, HANDLE) import System.Win32.Types (failIfNull, failIf, iNVALID_HANDLE_VALUE) import System.Win32.File (createFile,closeHandle, gENERIC_READ, fILE_SHARE_READ, oPEN_EXISTING, fILE_ATTRIBUTE_NORMAL, fILE_FLAG_BACKUP_SEMANTICS ) import System.Win32.DLL (loadLibrary, getProcAddress) #endif import System.Process import Control.Concurrent import FastString import SrcLoc ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan ) #ifdef 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 {- How GHC finds its files ~~~~~~~~~~~~~~~~~~~~~~~ [Note topdir] GHC needs various support files (library packages, RTS etc), plus various auxiliary programs (cp, gcc, etc). It starts by finding topdir, the root of GHC's support files On Unix: - ghc always has a shell wrapper that passes a -B