[commit: ghc] wip/angerman/win32-cross: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (e135e8c)
git at git.haskell.org
git at git.haskell.org
Mon Feb 26 06:12:56 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/angerman/win32-cross
Link : http://ghc.haskell.org/trac/ghc/changeset/e135e8c958fd57c4a027a74a2e13895af7a0910e/ghc
>---------------------------------------------------------------
commit e135e8c958fd57c4a027a74a2e13895af7a0910e
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date: Thu Feb 22 16:53:35 2018 +0800
Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv`
Summary:
This is done for consistency. We usually call the package file the same name the
folder has. The move into `utils` is done so that we can move the library into
`libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the
`iserv.cabal` apart. This will make building the cross compiler with TH
simpler, because we can build the library and proxy as separate packages.
Test Plan: ./validate
Reviewers: bgamari, goldfire, erikd
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4436
>---------------------------------------------------------------
e135e8c958fd57c4a027a74a2e13895af7a0910e
libraries/libiserv/src/Main.hs | 63 ------------------------------------------
1 file changed, 63 deletions(-)
diff --git a/libraries/libiserv/src/Main.hs b/libraries/libiserv/src/Main.hs
deleted file mode 100644
index 858cee8..0000000
--- a/libraries/libiserv/src/Main.hs
+++ /dev/null
@@ -1,63 +0,0 @@
-{-# LANGUAGE CPP, GADTs #-}
-
--- |
--- The Remote GHCi server.
---
--- For details on Remote GHCi, see Note [Remote GHCi] in
--- compiler/ghci/GHCi.hs.
---
-module Main (main) where
-
-import Lib (serv)
-
-import GHCi.Message
-import GHCi.Signals
-import GHCi.Utils
-
-import Control.Exception
-import Control.Monad
-import Data.IORef
-import System.Environment
-import System.Exit
-import Text.Printf
-
-dieWithUsage :: IO a
-dieWithUsage = do
- prog <- getProgName
- die $ prog ++ ": " ++ msg
- where
-#ifdef WINDOWS
- msg = "usage: iserv <write-handle> <read-handle> [-v]"
-#else
- msg = "usage: iserv <write-fd> <read-fd> [-v]"
-#endif
-
-main :: IO ()
-main = do
- args <- getArgs
- (wfd1, rfd2, rest) <-
- case args of
- arg0:arg1:rest -> do
- let wfd1 = read arg0
- rfd2 = read arg1
- return (wfd1, rfd2, rest)
- _ -> dieWithUsage
-
- verbose <- case rest of
- ["-v"] -> return True
- [] -> return False
- _ -> dieWithUsage
- when verbose $
- printf "GHC iserv starting (in: %d; out: %d)\n"
- (fromIntegral rfd2 :: Int) (fromIntegral wfd1 :: Int)
- inh <- getGhcHandle rfd2
- outh <- getGhcHandle wfd1
- installSignalHandlers
- lo_ref <- newIORef Nothing
- let pipe = Pipe{pipeRead = inh, pipeWrite = outh, pipeLeftovers = lo_ref}
- uninterruptibleMask $ serv verbose hook pipe
-
- where hook = return -- empty hook
- -- we cannot allow any async exceptions while communicating, because
- -- we will lose sync in the protocol, hence uninterruptibleMask.
-
More information about the ghc-commits
mailing list