{-# LINE 1 "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
-----------------------------------------------------------------------------

module System.Environment.ExecutablePath ( getExecutablePath ) where

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


{-# LINE 32 "System/Environment/ExecutablePath.hsc" #-}
import Foreign.C
import Foreign.Marshal.Array
import System.Posix.Internals

{-# LINE 60 "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.
--
-- 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.
--
-- @since 4.6.0.0
getExecutablePath :: IO FilePath

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


{-# LINE 125 "System/Environment/ExecutablePath.hsc" #-}

foreign import ccall unsafe "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 -> do
        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 -> do
            CInt
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
4096
            CStringLen -> 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"

--------------------------------------------------------------------------------
-- FreeBSD


{-# LINE 300 "System/Environment/ExecutablePath.hsc" #-}