File: Executable.hs

package info (click to toggle)
haskell-executable-path 0.0.3.1-7
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 88 kB
  • sloc: haskell: 421; makefile: 2
file content (160 lines) | stat: -rw-r--r-- 3,942 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160

{- |

The documentation of "System.Environment.getProgName" says that

\"However, this is hard-to-impossible to implement on some non-Unix OSes, 
so instead, for maximum portability, we just return the leafname 
of the program as invoked. Even then there are some differences 
between platforms: on Windows, for example, a program invoked as 
foo is probably really FOO.EXE, and that is what "getProgName" will 
return.\"

This library tries to fix this issue.
It also provides some platform-specific functions (most notably getting
the path of the application bundle on OSX). Supported operating
systems:
 
 * Win32 (tested on Windows 7)
 
 * Mac OS X
 
 * Linux

 * FreeBSD (tested on FreeBSD 6.4)

 * \*BSD (with procfs mounted, plus fallback for certain shells; untested)
 
 * Solaris (untested, and probably works on Solaris 10 only) 
 
-}

{-# LANGUAGE CPP #-}

module System.Environment.Executable
  ( getExecutablePath 
  , splitExecutablePath

#ifdef mingw32_HOST_OS 
  , getModulePath
#endif
 
#ifdef darwin_HOST_OS 
  , getApplicationBundlePath
#endif

#ifdef WE_HAVE_GHC
  , ScriptPath(..)
  , getScriptPath
#endif
  
  )
  where

import Control.Monad (liftM)
import System.FilePath (splitFileName)
import System.Directory (canonicalizePath)
import Data.Char (toLower)
import Data.List (find,findIndex)

#ifdef WE_HAVE_GHC
import GHC.Environment
#endif

--------------------------------------------------------------------------------

#ifdef mingw32_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Win32
#endif

#ifdef darwin_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.MacOSX
#endif

#ifdef linux_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Linux
#endif

#ifdef freebsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.FreeBSD
#endif

#ifdef netbsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.BSD
#endif

#ifdef openbsd_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.BSD
#endif

#ifdef solaris_HOST_OS
#define SUPPORTED_OS
import System.Environment.Executable.Solaris
#endif

--------------------------------------------------------------------------------

splitExecutablePath :: IO (FilePath,FilePath)
splitExecutablePath = liftM splitFileName getExecutablePath

--------------------------------------------------------------------------------

#ifndef SUPPORTED_OS
{-# WARNING getExecutablePath "the host OS is not supported!" #-}
getExecutablePath :: IO String
getExecutablePath = error "host OS not supported"
#endif

--------------------------------------------------------------------------------

#ifdef WE_HAVE_GHC

-- | 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"
            
data ScriptPath
  = Executable FilePath  -- ^ it was (probably) a proper compiled executable
  | RunGHC FilePath      -- ^ it was a script run by runghc/runhaskell
  | Interactive          -- ^ we are in GHCi
  deriving Show
  
#endif

--------------------------------------------------------------------------------