[commit: ghc] master: Modify getFullArgs to include program name (b093e63)
git at git.haskell.org
git at git.haskell.org
Tue Dec 29 14:04:59 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/b093e631fbef456a000107921d69b6b7b5845149/ghc
>---------------------------------------------------------------
commit b093e631fbef456a000107921d69b6b7b5845149
Author: Rik Steenkamp <rik at ewps.nl>
Date: Tue Dec 29 14:38:40 2015 +0100
Modify getFullArgs to include program name
Fixes an inconsistency of `getFullArgs` across operating systems. On
non-Windows systems the returning list did not include the program name
as the first element, while on Windows systems it did.
As `System.Environment` depends on this behaviour of `getFullArgs` under
Windows, this is now the behaviour across all operating systems.
Computation `getFullArgs` is now like the "raw" version of `getArgs`,
similar to `argv` in other languages.
This patch also fixes T10728 under Windows.
Reviewers: austin, hvr, erikd, #ghc_windows_task_force, Phyx, bgamari
Reviewed By: #ghc_windows_task_force, Phyx, bgamari
Subscribers: Phyx, thomie
Differential Revision: https://phabricator.haskell.org/D1713
>---------------------------------------------------------------
b093e631fbef456a000107921d69b6b7b5845149
libraries/base/GHC/Environment.hs | 18 +++++++++++-------
testsuite/tests/rts/T10728.hs | 2 +-
2 files changed, 12 insertions(+), 8 deletions(-)
diff --git a/libraries/base/GHC/Environment.hs b/libraries/base/GHC/Environment.hs
index 103848a..97005eb 100644
--- a/libraries/base/GHC/Environment.hs
+++ b/libraries/base/GHC/Environment.hs
@@ -20,9 +20,18 @@ import GHC.Windows
# else
# error Unknown mingw32 arch
# endif
+#else
+import GHC.IO.Encoding
+import qualified GHC.Foreign as GHC
+#endif
--- Ignore the arguments to hs_init on Windows for the sake of Unicode compat
+-- | Computation 'getFullArgs' is the "raw" version of 'getArgs', similar
+-- to @argv@ in other languages. It returns a list of the program's
+-- command line arguments, starting with the program name, and
+-- including those normally eaten by the RTS (+RTS ... -RTS).
getFullArgs :: IO [String]
+#ifdef mingw32_HOST_OS
+-- Ignore the arguments to hs_init on Windows for the sake of Unicode compat
getFullArgs = do
p_arg_string <- c_GetCommandLine
alloca $ \p_argc -> do
@@ -43,11 +52,6 @@ foreign import WINDOWS_CCONV unsafe "windows.h CommandLineToArgvW"
foreign import WINDOWS_CCONV unsafe "Windows.h LocalFree"
c_LocalFree :: Ptr a -> IO (Ptr a)
#else
-import GHC.IO.Encoding
-import GHC.Num
-import qualified GHC.Foreign as GHC
-
-getFullArgs :: IO [String]
getFullArgs =
alloca $ \ p_argc ->
alloca $ \ p_argv -> do
@@ -55,7 +59,7 @@ getFullArgs =
p <- fromIntegral `liftM` peek p_argc
argv <- peek p_argv
enc <- getFileSystemEncoding
- peekArray (p - 1) (advancePtr argv 1) >>= mapM (GHC.peekCString enc)
+ peekArray p argv >>= mapM (GHC.peekCString enc)
foreign import ccall unsafe "getFullProgArgv"
getFullProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()
diff --git a/testsuite/tests/rts/T10728.hs b/testsuite/tests/rts/T10728.hs
index 056124d..ff005fa 100644
--- a/testsuite/tests/rts/T10728.hs
+++ b/testsuite/tests/rts/T10728.hs
@@ -35,6 +35,6 @@ getN = getFullArgs >>= return . go
where
go :: [String] -> Int
go as = case reads (
- dropWhile (not . isDigit) . (!! 1) $ as ) :: [(Int, String)] of
+ dropWhile (not . isDigit) . (!! 2) $ as ) :: [(Int, String)] of
[x] -> fst x
_ -> 0
More information about the ghc-commits
mailing list