{-# LINE 1 "libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc" #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.Internal.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 base-4.6.0.0
-----------------------------------------------------------------------------

module GHC.Internal.System.Environment.ExecutablePath
  ( getExecutablePath
  , executablePath
  ) where

#if defined(javascript_HOST_ARCH)

import GHC.Internal.Base
import GHC.Internal.IO (FilePath)

getExecutablePath :: IO FilePath
getExecutablePath = return "a.jsexe"

executablePath :: Maybe (IO (Maybe FilePath))
executablePath = Nothing

#else

-- The imports are purposely kept completely disjoint to prevent edits
-- to one OS implementation from breaking another.

import GHC.Internal.Base
import GHC.Internal.IO (FilePath)
import GHC.Internal.Real

{-# LINE 44 "libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc" #-}
import GHC.Internal.Control.Exception (catch, throw)
import GHC.Internal.Word
import GHC.Internal.Foreign.C.Types
import GHC.Internal.Foreign.C.Error
import GHC.Internal.Foreign.C.String
import GHC.Internal.Foreign.Marshal.Alloc
import GHC.Internal.Foreign.Ptr
import GHC.Internal.Foreign.Storable
import GHC.Internal.System.IO.Error (isDoesNotExistError)
import GHC.Internal.System.Posix.Internals

{-# LINE 107 "libraries/ghc-internal/src/GHC/Internal/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 base-4.6.0.0
getExecutablePath :: 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, Solaris, 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.)
--
-- Note also that while most operating systems return @Nothing@ if the
-- executable file was deleted/unlinked, some (including NetBSD) return the
-- original path.
--
-- @since base-4.17.0.0
executablePath :: Maybe (IO (Maybe FilePath))


--------------------------------------------------------------------------------
-- Mac OS X


{-# LINE 155 "libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc" #-}

type UInt32 = Word32

foreign import ccall unsafe "mach-o/dyld.h _NSGetExecutablePath"
    c__NSGetExecutablePath :: CString -> Ptr UInt32 -> IO CInt

-- | Returns the path of the main executable. The path may be a
-- symbolic link and not the real file.
--
-- See dyld(3)
_NSGetExecutablePath :: IO FilePath
_NSGetExecutablePath =
    allocaBytes 1024 $ \ buf ->  -- PATH_MAX is 1024 on OS X
    alloca $ \ bufsize -> do
        poke bufsize 1024
        status <- c__NSGetExecutablePath buf bufsize
        if status == 0
            then peekFilePath buf
            else do reqBufsize <- fromIntegral `fmap` peek bufsize
                    allocaBytes reqBufsize $ \ newBuf -> do
                        status2 <- c__NSGetExecutablePath newBuf bufsize
                        if status2 == 0
                             then peekFilePath newBuf
                             else errorWithoutStackTrace "_NSGetExecutablePath: buffer too small"

foreign import ccall unsafe "stdlib.h realpath"
    c_realpath :: CString -> CString -> IO CString

-- | Resolves all symbolic links, extra \/ characters, and references
-- to \/.\/ and \/..\/. Returns an absolute pathname.
--
-- See realpath(3)
realpath :: FilePath -> IO FilePath
realpath path =
    withFilePath path $ \ fileName ->
    allocaBytes 1024 $ \ resolvedName -> do
        _ <- throwErrnoIfNull "realpath" $ c_realpath fileName resolvedName
        peekFilePath resolvedName

getExecutablePath = _NSGetExecutablePath >>= realpath

-- realpath(3) fails with ENOENT file does not exist (e.g. was deleted)
executablePath = Just (fmap Just getExecutablePath `catch` f)
  where
  f e | isDoesNotExistError e = pure Nothing
      | otherwise             = throw e

--------------------------------------------------------------------------------
-- Linux / Solaris


{-# LINE 426 "libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc" #-}

#endif