{-# LINE 1 "libraries/base/System/Environment/ExecutablePath.hsc" #-}{-# LANGUAGE Safe #-}{-# LANGUAGE CPP #-}------------------------------------------------------------------------------- |-- Module : System.Environment.ExecutablePath-- Copyright : (c) The University of Glasgow 2001-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : portable---- Function to retrieve the absolute filepath of the current executable.---- @since 4.6.0.0-----------------------------------------------------------------------------moduleSystem.Environment.ExecutablePath(getExecutablePath ,executablePath )where-- The imports are purposely kept completely disjoint to prevent edits-- to one OS implementation from breaking another.{-# LINE 37 "libraries/base/System/Environment/ExecutablePath.hsc" #-}importData.List (isSuffixOf )importForeign.C importForeign.Marshal.Array importSystem.Posix.Internals {-# LINE 69 "libraries/base/System/Environment/ExecutablePath.hsc" #-}-- The exported function is defined outside any if-guard to make sure-- every OS implements it with the same type.-- | Returns the absolute pathname of the current executable,-- or @argv[0]@ if the operating system does not provide a reliable-- way query the current executable.---- Note that for scripts and interactive sessions, this is the path to-- the interpreter (e.g. ghci.)---- Since base 4.11.0.0, 'getExecutablePath' resolves symlinks on Windows.-- If an executable is launched through a symlink, 'getExecutablePath'-- returns the absolute path of the original executable.---- If the executable has been deleted, behaviour is ill-defined and-- varies by operating system. See 'executablePath' for a more-- reliable way to query the current executable.---- @since 4.6.0.0getExecutablePath ::IO FilePath -- | Get an action to query the absolute pathname of the current executable.---- If the operating system provides a reliable way to determine the current-- executable, return the query action, otherwise return @Nothing@. The action-- is defined on FreeBSD, Linux, MacOS, NetBSD, and Windows.---- Even where the query action is defined, there may be situations where no-- result is available, e.g. if the executable file was deleted while the-- program is running. Therefore the result of the query action is a @Maybe-- FilePath@.---- Note that for scripts and interactive sessions, the result is the path to-- the interpreter (e.g. ghci.)---- @since 4.17.0.0executablePath ::Maybe (IO (Maybe FilePath ))---------------------------------------------------------------------------------- Mac OS X{-# LINE 164 "libraries/base/System/Environment/ExecutablePath.hsc" #-}foreignimportccallunsafe"readlink"c_readlink ::CString ->CString ->CSize ->IO CInt -- | Reads the @FilePath@ pointed to by the symbolic link and returns-- it.---- See readlink(2)readSymbolicLink ::FilePath ->IO FilePath readSymbolicLink :: FilePath -> IO FilePath
readSymbolicLink FilePath
file =Int -> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray0 Int
4096((Ptr CChar -> IO FilePath) -> IO FilePath)
-> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
buf ->FilePath -> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePath FilePath
file ((Ptr CChar -> IO FilePath) -> IO FilePath)
-> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
s ->doCInt
len <-FilePath -> FilePath -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO a
throwErrnoPathIfMinus1 FilePath
"readSymbolicLink"FilePath
file (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr CChar -> Ptr CChar -> CSize -> IO CInt
c_readlink Ptr CChar
s Ptr CChar
buf CSize
4096CStringLen -> IO FilePath
peekFilePathLen (Ptr CChar
buf ,CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len )getExecutablePath :: IO FilePath
getExecutablePath =FilePath -> IO FilePath
readSymbolicLink (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"/proc/self/exe"executablePath :: Maybe (IO (Maybe FilePath))
executablePath =IO (Maybe FilePath) -> Maybe (IO (Maybe FilePath))
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath
check (FilePath -> Maybe FilePath) -> IO FilePath -> IO (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getExecutablePath )where-- procfs(5): If the pathname has been unlinked, the symbolic link will-- contain the string '(deleted)' appended to the original pathname.---- See also https://gitlab.haskell.org/ghc/ghc/-/issues/10957check :: FilePath -> Maybe FilePath
check FilePath
s |FilePath
"(deleted)"FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` FilePath
s =Maybe FilePath
forall a. Maybe a
Nothing |Bool
otherwise =FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
s ---------------------------------------------------------------------------------- FreeBSD / NetBSD{-# LINE 371 "libraries/base/System/Environment/ExecutablePath.hsc" #-}

AltStyle によって変換されたページ (->オリジナル) /