Proposal: Add getFullProgName

Johan Tibell johan.tibell at gmail.com
Mon Jun 18 20:36:06 CEST 2012


On Sun, Jun 17, 2012 at 2:20 AM, Heinrich Apfelmus
<apfelmus at quantentunnel.de> wrote:
> Johan Tibell wrote:
>>
>> I've modified the proposal (in an earlier email) to be to add
>> getExecutablePath. We'll implement it using the methods Simon linked
>> to, which I believe are the same as used in executable-path.
>
>
> Ah, ok. That works for me.
>
> Reading Simon Hengel's email, I think that distinguishing between different
> invocation methods (program, script, interactive) via a data type
>
>
>    data ExecutablePath = Binary FilePath
>                        | Script FilePath
>                        | Interactive
>
> is an excellent idea! This allows us to use the  getExecutablePath  both in
> a compiled program and for testing in GHCi.

I'm a bit undecided whether this distinction is useful. If the user is
really looking for the executable path there's not much to do except
call error if the return value is Script or Interactive.

In addition, I don't know how to implement this function correctly.
For example, if you alias ghc to another name the heuristic in the
executable-path package fails:

-- | An experimental hack which tries to figure out if the program
-- was run with @runghc@ or @runhaskell@ or @ghci@, and then tries to find
-- out the directory of the /source/ (or object file).
--
-- GHC only.
getScriptPath :: IO ScriptPath
getScriptPath = do
  fargs <- getFullArgs
  exec  <- getExecutablePath
  let (pt,fn) = splitFileName exec
  case fargs of
    [] -> return (Executable exec)
    _  -> case map toLower fn of
#ifdef mingw32_HOST_OS
      "ghc.exe" -> do
#else
      "ghc" -> do
#endif
        case find f1 fargs of
          Just s  -> do
            path <- canonicalizePath $ init (drop n1 s)
            return $ RunGHC path
          Nothing -> case findIndex f2 fargs of
            Just i  -> return Interactive
            Nothing -> return (Executable exec)
      _ -> return (Executable exec)

  where
    f1 xs = take n1 xs == s1
    s1 = ":set prog \""
    n1 = length s1

    f2 xs = xs == "--interactive"



More information about the Libraries mailing list