{-# LANGUAGE CPP #-}
module GHC.SysTools.Process where
#include "HsVersions.h"
import GHC.Utils.Exception
import GHC.Utils.Error
import GHC.Driver.Session
import GHC.Data.FastString
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Prelude
import GHC.Utils.Misc
import GHC.Types.SrcLoc ( SrcLoc, mkSrcLoc, noSrcSpan, mkSrcSpan )
import Control.Concurrent
import Data.Char
import System.Exit
import System.Environment
import System.FilePath
import System.IO
import System.IO.Error as IO
import System.Process
import GHC.SysTools.FileCleanup
enableProcessJobs :: CreateProcess -> CreateProcess
#if defined(MIN_VERSION_process)
#if MIN_VERSION_process(1,6,9)
enableProcessJobs :: CreateProcess -> CreateProcess
enableProcessJobs CreateProcess
opts = CreateProcess
opts { use_process_jobs :: Bool
use_process_jobs = Bool
True }
#else
enableProcessJobs opts = opts
#endif
#else
enableProcessJobs opts = opts
#endif
readCreateProcessWithExitCode'
:: CreateProcess
-> IO (ExitCode, String)
readCreateProcessWithExitCode' :: CreateProcess -> IO (ExitCode, String)
readCreateProcessWithExitCode' CreateProcess
proc = do
(Maybe Handle
_, Just Handle
outh, Maybe Handle
_, ProcessHandle
pid) <-
CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess (CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle))
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
forall a b. (a -> b) -> a -> b
$ CreateProcess -> CreateProcess
enableProcessJobs (CreateProcess -> CreateProcess) -> CreateProcess -> CreateProcess
forall a b. (a -> b) -> a -> b
$ CreateProcess
proc{ std_out :: StdStream
std_out = StdStream
CreatePipe }
String
output <- Handle -> IO String
hGetContents Handle
outh
MVar ()
outMVar <- IO (MVar ())
forall a. IO (MVar a)
newEmptyMVar
ThreadId
_ <- IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ Int -> IO Int
forall a. a -> IO a
evaluate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
output) IO Int -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MVar () -> () -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar ()
outMVar ()
MVar () -> IO ()
forall a. MVar a -> IO a
takeMVar MVar ()
outMVar
Handle -> IO ()
hClose Handle
outh
ExitCode
ex <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
(ExitCode, String) -> IO (ExitCode, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
ex, String
output)
replaceVar :: (String, String) -> [(String, String)] -> [(String, String)]
replaceVar :: (String, String) -> [(String, String)] -> [(String, String)]
replaceVar (String
var, String
value) [(String, String)]
env =
(String
var, String
value) (String, String) -> [(String, String)] -> [(String, String)]
forall a. a -> [a] -> [a]
: ((String, String) -> Bool)
-> [(String, String)] -> [(String, String)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(String
var',String
_) -> String
var String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
var') [(String, String)]
env
readProcessEnvWithExitCode
:: String
-> [String]
-> (String, String)
-> IO (ExitCode, String, String)
readProcessEnvWithExitCode :: String
-> [String] -> (String, String) -> IO (ExitCode, String, String)
readProcessEnvWithExitCode String
prog [String]
args (String, String)
env_update = do
[(String, String)]
current_env <- IO [(String, String)]
getEnvironment
CreateProcess -> String -> IO (ExitCode, String, String)
readCreateProcessWithExitCode (String -> [String] -> CreateProcess
proc String
prog [String]
args) {
env :: Maybe [(String, String)]
env = [(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just ((String, String) -> [(String, String)] -> [(String, String)]
replaceVar (String, String)
env_update [(String, String)]
current_env) } String
""
c_locale_env :: (String, String)
c_locale_env :: (String, String)
c_locale_env = (String
"LANGUAGE", String
"C")
getGccEnv :: [Option] -> IO (Maybe [(String,String)])
getGccEnv :: [Option] -> IO (Maybe [(String, String)])
getGccEnv [Option]
opts =
if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
b_dirs
then Maybe [(String, String)] -> IO (Maybe [(String, String)])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [(String, String)]
forall a. Maybe a
Nothing
else do [(String, String)]
env <- IO [(String, String)]
getEnvironment
Maybe [(String, String)] -> IO (Maybe [(String, String)])
forall (m :: * -> *) a. Monad m => a -> m a
return ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just ([(String, String)] -> [(String, String)]
forall {a}. a -> a
mangle_paths [(String, String)]
env))
where
([String]
b_dirs, [Option]
_) = (Option -> Either String Option)
-> [Option] -> ([String], [Option])
forall a b c. (a -> Either b c) -> [a] -> ([b], [c])
partitionWith Option -> Either String Option
get_b_opt [Option]
opts
get_b_opt :: Option -> Either String Option
get_b_opt (Option (Char
'-':Char
'B':String
dir)) = String -> Either String Option
forall a b. a -> Either a b
Left String
dir
get_b_opt Option
other = Option -> Either String Option
forall a b. b -> Either a b
Right Option
other
#if defined(mingw32_HOST_OS)
mangle_paths = map mangle_path
mangle_path (path,paths) | map toUpper path == "PATH"
= (path, '\"' : head b_dirs ++ "\";" ++ paths)
mangle_path other = other
#else
mangle_paths :: a -> a
mangle_paths = a -> a
forall {a}. a -> a
id
#endif
runSomething :: DynFlags
-> String
-> String
-> [Option]
-> IO ()
runSomething :: DynFlags -> String -> String -> [Option] -> IO ()
runSomething DynFlags
dflags String
phase_name String
pgm [Option]
args =
DynFlags
-> (String -> String)
-> String
-> String
-> [Option]
-> Maybe String
-> Maybe [(String, String)]
-> IO ()
runSomethingFiltered DynFlags
dflags String -> String
forall {a}. a -> a
id String
phase_name String
pgm [Option]
args Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
forall a. Maybe a
Nothing
runSomethingResponseFile
:: DynFlags -> (String->String) -> String -> String -> [Option]
-> Maybe [(String,String)] -> IO ()
runSomethingResponseFile :: DynFlags
-> (String -> String)
-> String
-> String
-> [Option]
-> Maybe [(String, String)]
-> IO ()
runSomethingResponseFile DynFlags
dflags String -> String
filter_fn String
phase_name String
pgm [Option]
args Maybe [(String, String)]
mb_env =
DynFlags
-> String
-> String
-> [Option]
-> ([String] -> IO (ExitCode, ()))
-> IO ()
forall a.
DynFlags
-> String
-> String
-> [Option]
-> ([String] -> IO (ExitCode, a))
-> IO a
runSomethingWith DynFlags
dflags String
phase_name String
pgm [Option]
args (([String] -> IO (ExitCode, ())) -> IO ())
-> ([String] -> IO (ExitCode, ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \[String]
real_args -> do
String
fp <- [String] -> IO String
forall {t :: * -> *}. Foldable t => [t Char] -> IO String
getResponseFile [String]
real_args
let args :: [String]
args = [Char
'@'Char -> String -> String
forall a. a -> [a] -> [a]
:String
fp]
ExitCode
r <- DynFlags
-> (String -> String)
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO ExitCode
builderMainLoop DynFlags
dflags String -> String
filter_fn String
pgm [String]
args Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
mb_env
(ExitCode, ()) -> IO (ExitCode, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
r,())
where
getResponseFile :: [t Char] -> IO String
getResponseFile [t Char]
args = do
String
fp <- DynFlags -> TempFileLifetime -> String -> IO String
newTempName DynFlags
dflags TempFileLifetime
TFL_CurrentModule String
"rsp"
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
fp IOMode
WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
#if defined(mingw32_HOST_OS)
hSetEncoding h latin1
#else
Handle -> TextEncoding -> IO ()
hSetEncoding Handle
h TextEncoding
utf8
#endif
Handle -> String -> IO ()
hPutStr Handle
h (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (t Char -> String) -> [t Char] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map t Char -> String
forall {t :: * -> *}. Foldable t => t Char -> String
escape [t Char]
args
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
fp
escape :: t Char -> String
escape t Char
x = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"\""
, (Char -> String) -> t Char -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
(\Char
c ->
case Char
c of
Char
'\\' -> String
"\\\\"
Char
'\n' -> String
"\\n"
Char
'\"' -> String
"\\\""
Char
_ -> [Char
c])
t Char
x
, String
"\""
]
runSomethingFiltered
:: DynFlags -> (String->String) -> String -> String -> [Option]
-> Maybe FilePath -> Maybe [(String,String)] -> IO ()
runSomethingFiltered :: DynFlags
-> (String -> String)
-> String
-> String
-> [Option]
-> Maybe String
-> Maybe [(String, String)]
-> IO ()
runSomethingFiltered DynFlags
dflags String -> String
filter_fn String
phase_name String
pgm [Option]
args Maybe String
mb_cwd Maybe [(String, String)]
mb_env = do
DynFlags
-> String
-> String
-> [Option]
-> ([String] -> IO (ExitCode, ()))
-> IO ()
forall a.
DynFlags
-> String
-> String
-> [Option]
-> ([String] -> IO (ExitCode, a))
-> IO a
runSomethingWith DynFlags
dflags String
phase_name String
pgm [Option]
args (([String] -> IO (ExitCode, ())) -> IO ())
-> ([String] -> IO (ExitCode, ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \[String]
real_args -> do
ExitCode
r <- DynFlags
-> (String -> String)
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO ExitCode
builderMainLoop DynFlags
dflags String -> String
filter_fn String
pgm [String]
real_args Maybe String
mb_cwd Maybe [(String, String)]
mb_env
(ExitCode, ()) -> IO (ExitCode, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
r,())
runSomethingWith
:: DynFlags -> String -> String -> [Option]
-> ([String] -> IO (ExitCode, a))
-> IO a
runSomethingWith :: forall a.
DynFlags
-> String
-> String
-> [Option]
-> ([String] -> IO (ExitCode, a))
-> IO a
runSomethingWith DynFlags
dflags String
phase_name String
pgm [Option]
args [String] -> IO (ExitCode, a)
io = do
let real_args :: [String]
real_args = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
forall a. [a] -> Bool
notNull ((Option -> String) -> [Option] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Option -> String
showOpt [Option]
args)
cmdLine :: String
cmdLine = String -> [String] -> String
showCommandForUser String
pgm [String]
real_args
DynFlags -> String -> String -> IO a -> IO a
forall a. DynFlags -> String -> String -> IO a -> IO a
traceCmd DynFlags
dflags String
phase_name String
cmdLine (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ String -> String -> IO (ExitCode, a) -> IO a
forall r. String -> String -> IO (ExitCode, r) -> IO r
handleProc String
pgm String
phase_name (IO (ExitCode, a) -> IO a) -> IO (ExitCode, a) -> IO a
forall a b. (a -> b) -> a -> b
$ [String] -> IO (ExitCode, a)
io [String]
real_args
handleProc :: String -> String -> IO (ExitCode, r) -> IO r
handleProc :: forall r. String -> String -> IO (ExitCode, r) -> IO r
handleProc String
pgm String
phase_name IO (ExitCode, r)
proc = do
(ExitCode
rc, r
r) <- IO (ExitCode, r)
proc IO (ExitCode, r)
-> (IOException -> IO (ExitCode, r)) -> IO (ExitCode, r)
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` IOException -> IO (ExitCode, r)
forall {a}. IOException -> IO a
handler
case ExitCode
rc of
ExitSuccess{} -> r -> IO r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
ExitFailure Int
n -> GhcException -> IO r
forall a. GhcException -> IO a
throwGhcExceptionIO (
String -> GhcException
ProgramError (String
"`" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
takeFileName String
pgm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" failed in phase `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
phase_name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'." String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" (Exit code: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"))
where
handler :: IOException -> IO a
handler IOException
err =
if IOException -> Bool
IO.isDoesNotExistError IOException
err
then IO a
forall {a}. IO a
does_not_exist
else GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (String -> GhcException) -> String -> GhcException
forall a b. (a -> b) -> a -> b
$ IOException -> String
forall a. Show a => a -> String
show IOException
err)
does_not_exist :: IO a
does_not_exist = GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
InstallationError (String
"could not execute: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
pgm))
builderMainLoop :: DynFlags -> (String -> String) -> FilePath
-> [String] -> Maybe FilePath -> Maybe [(String, String)]
-> IO ExitCode
builderMainLoop :: DynFlags
-> (String -> String)
-> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> IO ExitCode
builderMainLoop DynFlags
dflags String -> String
filter_fn String
pgm [String]
real_args Maybe String
mb_cwd Maybe [(String, String)]
mb_env = do
Chan BuildMessage
chan <- IO (Chan BuildMessage)
forall a. IO (Chan a)
newChan
let safely :: (ProcessHandle -> IO b) -> IO b
safely ProcessHandle -> IO b
inner = ((forall a. IO a -> IO a) -> IO b) -> IO b
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO b) -> IO b)
-> ((forall a. IO a -> IO a) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> do
let procdata :: CreateProcess
procdata =
CreateProcess -> CreateProcess
enableProcessJobs
(CreateProcess -> CreateProcess) -> CreateProcess -> CreateProcess
forall a b. (a -> b) -> a -> b
$ (String -> [String] -> CreateProcess
proc String
pgm [String]
real_args) { cwd :: Maybe String
cwd = Maybe String
mb_cwd
, env :: Maybe [(String, String)]
env = Maybe [(String, String)]
mb_env
, std_in :: StdStream
std_in = StdStream
CreatePipe
, std_out :: StdStream
std_out = StdStream
CreatePipe
, std_err :: StdStream
std_err = StdStream
CreatePipe
}
(Just Handle
hStdIn, Just Handle
hStdOut, Just Handle
hStdErr, ProcessHandle
hProcess) <- IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
forall a. IO a -> IO a
restore (IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle))
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
forall a b. (a -> b) -> a -> b
$
String
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess_ String
"builderMainLoop" CreateProcess
procdata
let cleanup_handles :: IO ()
cleanup_handles = do
Handle -> IO ()
hClose Handle
hStdIn
Handle -> IO ()
hClose Handle
hStdOut
Handle -> IO ()
hClose Handle
hStdErr
Either SomeException b
r <- IO b -> IO (Either SomeException b)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO b -> IO (Either SomeException b))
-> IO b -> IO (Either SomeException b)
forall a b. (a -> b) -> a -> b
$ IO b -> IO b
forall a. IO a -> IO a
restore (IO b -> IO b) -> IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
Handle -> BufferMode -> IO ()
hSetBuffering Handle
hStdOut BufferMode
LineBuffering
Handle -> BufferMode -> IO ()
hSetBuffering Handle
hStdErr BufferMode
LineBuffering
let make_reader_proc :: Handle -> IO ThreadId
make_reader_proc Handle
h = IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ Chan BuildMessage -> Handle -> (String -> String) -> IO ()
readerProc Chan BuildMessage
chan Handle
h String -> String
filter_fn
IO ThreadId -> (ThreadId -> IO ()) -> (ThreadId -> IO b) -> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError (Handle -> IO ThreadId
make_reader_proc Handle
hStdOut) ThreadId -> IO ()
killThread ((ThreadId -> IO b) -> IO b) -> (ThreadId -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \ThreadId
_ ->
IO ThreadId -> (ThreadId -> IO ()) -> (ThreadId -> IO b) -> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError (Handle -> IO ThreadId
make_reader_proc Handle
hStdErr) ThreadId -> IO ()
killThread ((ThreadId -> IO b) -> IO b) -> (ThreadId -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \ThreadId
_ ->
ProcessHandle -> IO b
inner ProcessHandle
hProcess
case Either SomeException b
r of
Left (SomeException e
e) -> do
ProcessHandle -> IO ()
terminateProcess ProcessHandle
hProcess
IO ()
cleanup_handles
e -> IO b
forall a e. Exception e => e -> a
throw e
e
Right b
s -> do
IO ()
cleanup_handles
b -> IO b
forall (m :: * -> *) a. Monad m => a -> m a
return b
s
(ProcessHandle -> IO ExitCode) -> IO ExitCode
forall {b}. (ProcessHandle -> IO b) -> IO b
safely ((ProcessHandle -> IO ExitCode) -> IO ExitCode)
-> (ProcessHandle -> IO ExitCode) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ \ProcessHandle
h -> do
Chan BuildMessage -> Integer -> IO ()
forall {a}. (Eq a, Num a) => Chan BuildMessage -> a -> IO ()
log_loop Chan BuildMessage
chan (Integer
2 :: Integer)
ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
h
where
log_loop :: Chan BuildMessage -> a -> IO ()
log_loop Chan BuildMessage
_ a
0 = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
log_loop Chan BuildMessage
chan a
t = do
BuildMessage
msg <- Chan BuildMessage -> IO BuildMessage
forall a. Chan a -> IO a
readChan Chan BuildMessage
chan
case BuildMessage
msg of
BuildMsg SDoc
msg -> do
DynFlags -> WarnReason -> Severity -> SrcSpan -> SDoc -> IO ()
putLogMsg DynFlags
dflags WarnReason
NoReason Severity
SevInfo SrcSpan
noSrcSpan
(SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle SDoc
msg
Chan BuildMessage -> a -> IO ()
log_loop Chan BuildMessage
chan a
t
BuildError SrcLoc
loc SDoc
msg -> do
DynFlags -> WarnReason -> Severity -> SrcSpan -> SDoc -> IO ()
putLogMsg DynFlags
dflags WarnReason
NoReason Severity
SevError (SrcLoc -> SrcLoc -> SrcSpan
mkSrcSpan SrcLoc
loc SrcLoc
loc)
(SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle SDoc
msg
Chan BuildMessage -> a -> IO ()
log_loop Chan BuildMessage
chan a
t
BuildMessage
EOF ->
Chan BuildMessage -> a -> IO ()
log_loop Chan BuildMessage
chan (a
ta -> a -> a
forall a. Num a => a -> a -> a
-a
1)
readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
readerProc :: Chan BuildMessage -> Handle -> (String -> String) -> IO ()
readerProc Chan BuildMessage
chan Handle
hdl String -> String
filter_fn =
(do String
str <- Handle -> IO String
hGetContents Handle
hdl
[String] -> Maybe BuildMessage -> IO ()
loop (String -> [String]
linesPlatform (String -> String
filter_fn String
str)) Maybe BuildMessage
forall a. Maybe a
Nothing)
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
`finally`
Chan BuildMessage -> BuildMessage -> IO ()
forall a. Chan a -> a -> IO ()
writeChan Chan BuildMessage
chan BuildMessage
EOF
where
loop :: [String] -> Maybe BuildMessage -> IO ()
loop [] Maybe BuildMessage
Nothing = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
loop [] (Just BuildMessage
err) = Chan BuildMessage -> BuildMessage -> IO ()
forall a. Chan a -> a -> IO ()
writeChan Chan BuildMessage
chan BuildMessage
err
loop (String
l:[String]
ls) Maybe BuildMessage
in_err =
case Maybe BuildMessage
in_err of
Just err :: BuildMessage
err@(BuildError SrcLoc
srcLoc SDoc
msg)
| String -> Bool
leading_whitespace String
l -> do
[String] -> Maybe BuildMessage -> IO ()
loop [String]
ls (BuildMessage -> Maybe BuildMessage
forall a. a -> Maybe a
Just (SrcLoc -> SDoc -> BuildMessage
BuildError SrcLoc
srcLoc (SDoc
msg SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
l)))
| Bool
otherwise -> do
Chan BuildMessage -> BuildMessage -> IO ()
forall a. Chan a -> a -> IO ()
writeChan Chan BuildMessage
chan BuildMessage
err
String -> [String] -> IO ()
checkError String
l [String]
ls
Maybe BuildMessage
Nothing -> do
String -> [String] -> IO ()
checkError String
l [String]
ls
Maybe BuildMessage
_ -> String -> IO ()
forall a. String -> a
panic String
"readerProc/loop"
checkError :: String -> [String] -> IO ()
checkError String
l [String]
ls
= case String -> Maybe (String, Int, Int, String)
parseError String
l of
Maybe (String, Int, Int, String)
Nothing -> do
Chan BuildMessage -> BuildMessage -> IO ()
forall a. Chan a -> a -> IO ()
writeChan Chan BuildMessage
chan (SDoc -> BuildMessage
BuildMsg (String -> SDoc
text String
l))
[String] -> Maybe BuildMessage -> IO ()
loop [String]
ls Maybe BuildMessage
forall a. Maybe a
Nothing
Just (String
file, Int
lineNum, Int
colNum, String
msg) -> do
let srcLoc :: SrcLoc
srcLoc = FastString -> Int -> Int -> SrcLoc
mkSrcLoc (String -> FastString
mkFastString String
file) Int
lineNum Int
colNum
[String] -> Maybe BuildMessage -> IO ()
loop [String]
ls (BuildMessage -> Maybe BuildMessage
forall a. a -> Maybe a
Just (SrcLoc -> SDoc -> BuildMessage
BuildError SrcLoc
srcLoc (String -> SDoc
text String
msg)))
leading_whitespace :: String -> Bool
leading_whitespace [] = Bool
False
leading_whitespace (Char
x:String
_) = Char -> Bool
isSpace Char
x
parseError :: String -> Maybe (String, Int, Int, String)
parseError :: String -> Maybe (String, Int, Int, String)
parseError String
s0 = case String -> Maybe (String, String)
breakColon String
s0 of
Just (String
filename, String
s1) ->
case String -> Maybe (Int, String)
breakIntColon String
s1 of
Just (Int
lineNum, String
s2) ->
case String -> Maybe (Int, String)
breakIntColon String
s2 of
Just (Int
columnNum, String
s3) ->
(String, Int, Int, String) -> Maybe (String, Int, Int, String)
forall a. a -> Maybe a
Just (String
filename, Int
lineNum, Int
columnNum, String
s3)
Maybe (Int, String)
Nothing ->
(String, Int, Int, String) -> Maybe (String, Int, Int, String)
forall a. a -> Maybe a
Just (String
filename, Int
lineNum, Int
0, String
s2)
Maybe (Int, String)
Nothing -> Maybe (String, Int, Int, String)
forall a. Maybe a
Nothing
Maybe (String, String)
Nothing -> Maybe (String, Int, Int, String)
forall a. Maybe a
Nothing
breakColon :: String -> Maybe (String, String)
breakColon :: String -> Maybe (String, String)
breakColon = String -> String -> Maybe (String, String)
go []
where
go :: String -> String -> Maybe (String, String)
go String
accum (Char
':':Char
'\\':String
rest) = String -> String -> Maybe (String, String)
go (Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
':'Char -> String -> String
forall a. a -> [a] -> [a]
:String
accum) String
rest
go String
accum (Char
':':Char
'/':String
rest) = String -> String -> Maybe (String, String)
go (Char
'/'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
':'Char -> String -> String
forall a. a -> [a] -> [a]
:String
accum) String
rest
go String
accum (Char
':':String
rest) = (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just (String -> String
forall a. [a] -> [a]
reverse String
accum, String
rest)
go String
accum (Char
c:String
rest) = String -> String -> Maybe (String, String)
go (Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:String
accum) String
rest
go String
_accum [] = Maybe (String, String)
forall a. Maybe a
Nothing
breakIntColon :: String -> Maybe (Int, String)
breakIntColon :: String -> Maybe (Int, String)
breakIntColon String
xs = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char
':' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==) String
xs of
(String
ys, Char
_:String
zs)
| Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ys) Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAscii String
ys Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit String
ys ->
(Int, String) -> Maybe (Int, String)
forall a. a -> Maybe a
Just (String -> Int
forall a. Read a => String -> a
read String
ys, String
zs)
(String, String)
_ -> Maybe (Int, String)
forall a. Maybe a
Nothing
data BuildMessage
= BuildMsg !SDoc
| BuildError !SrcLoc !SDoc
| EOF
linesPlatform :: String -> [String]
#if !defined(mingw32_HOST_OS)
linesPlatform :: String -> [String]
linesPlatform String
ls = String -> [String]
lines String
ls
#else
linesPlatform "" = []
linesPlatform xs =
case lineBreak xs of
(as,xs1) -> as : linesPlatform xs1
where
lineBreak "" = ("","")
lineBreak ('\r':'\n':xs) = ([],xs)
lineBreak ('\n':xs) = ([],xs)
lineBreak (x:xs) = let (as,bs) = lineBreak xs in (x:as,bs)
#endif