[commit: ghc] master: iserv: Show usage message on argument parse failure (3005fa5)
git at git.haskell.org
git at git.haskell.org
Wed Aug 31 17:19:35 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3005fa5313b6d5fd9d4f47192c84e96e94ee7f17/ghc
>---------------------------------------------------------------
commit 3005fa5313b6d5fd9d4f47192c84e96e94ee7f17
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Tue Aug 30 17:06:08 2016 -0400
iserv: Show usage message on argument parse failure
Test Plan: validate
Reviewers: simonmar, erikd, austin
Reviewed By: simonmar, erikd
Subscribers: thomie, erikd
Differential Revision: https://phabricator.haskell.org/D2494
GHC Trac Issues: #12491
>---------------------------------------------------------------
3005fa5313b6d5fd9d4f47192c84e96e94ee7f17
iserv/iserv-bin.cabal | 4 +++-
iserv/src/Main.hs | 26 ++++++++++++++++++++++----
2 files changed, 25 insertions(+), 5 deletions(-)
diff --git a/iserv/iserv-bin.cabal b/iserv/iserv-bin.cabal
index 3fd5d2b..eb33277 100644
--- a/iserv/iserv-bin.cabal
+++ b/iserv/iserv-bin.cabal
@@ -26,5 +26,7 @@ Executable iserv
deepseq >= 1.4 && < 1.5,
ghci == 8.1
- if !os(windows)
+ if os(windows)
+ Cpp-Options: -DWINDOWS
+ else
Build-Depends: unix >= 2.7 && < 2.8
diff --git a/iserv/src/Main.hs b/iserv/src/Main.hs
index 66e15c9..8c76e1f 100644
--- a/iserv/src/Main.hs
+++ b/iserv/src/Main.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecordWildCards, GADTs, ScopedTypeVariables, RankNTypes #-}
+{-# LANGUAGE CPP, RecordWildCards, GADTs, ScopedTypeVariables, RankNTypes #-}
-- |
-- The Remote GHCi server.
@@ -23,14 +23,32 @@ 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
- (arg0:arg1:rest) <- getArgs
- let wfd1 = read arg0; rfd2 = read arg1
+ 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
- _ -> die "iserv: syntax: iserv <write-fd> <read-fd> [-v]"
+ _ -> dieWithUsage
when verbose $ do
printf "GHC iserv starting (in: %d; out: %d)\n"
(fromIntegral rfd2 :: Int) (fromIntegral wfd1 :: Int)
More information about the ghc-commits
mailing list