Skip to content
Snippets Groups Projects
Commit 4dfc4d2d authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Implement GHC.Environment.getFullArgs

This returns all the arguments, including those normally eaten by the
RTS (+RTS ... -RTS).
This is mainly for ghc-inplace, where we need to pass /all/ the
arguments on to the real ghc. e.g. ioref001(ghci) was failing because
the +RTS -K32m -RTS wasn't getting passed on.
parent d1e92c04
No related branches found
No related tags found
No related merge requests found
module GHC.Environment (getFullArgs) where
import Prelude
import Foreign
import Foreign.C
import Control.Monad
getFullArgs :: IO [String]
getFullArgs =
alloca $ \ p_argc ->
alloca $ \ p_argv -> do
getFullProgArgv p_argc p_argv
p <- fromIntegral `liftM` peek p_argc
argv <- peek p_argv
peekArray (p - 1) (advancePtr argv 1) >>= mapM peekCString
foreign import ccall unsafe "getFullProgArgv"
getFullProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()
...@@ -106,6 +106,7 @@ exposed-modules: ...@@ -106,6 +106,7 @@ exposed-modules:
GHC.ConsoleHandler, GHC.ConsoleHandler,
GHC.Dotnet, GHC.Dotnet,
GHC.Enum, GHC.Enum,
GHC.Environment,
GHC.Err, GHC.Err,
GHC.Exception, GHC.Exception,
GHC.Exts, GHC.Exts,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment