{-# LINE 1 "System/Environment/ExecutablePath.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
module System.Environment.ExecutablePath ( getExecutablePath ) where
{-# LINE 32 "System/Environment/ExecutablePath.hsc" #-}
import Foreign.C
import Foreign.Marshal.Array
import System.Posix.Internals
{-# LINE 60 "System/Environment/ExecutablePath.hsc" #-}
getExecutablePath :: IO FilePath
{-# LINE 125 "System/Environment/ExecutablePath.hsc" #-}
foreign import ccall unsafe "readlink"
c_readlink :: CString -> CString -> CSize -> IO CInt
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"
{-# LINE 300 "System/Environment/ExecutablePath.hsc" #-}