{-# LINE 1 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
module System.Environment.ExecutablePath
( getExecutablePath
#if !defined(javascript_HOST_ARCH)
, executablePath
#endif
) where
#if defined(javascript_HOST_ARCH)
getExecutablePath :: IO FilePath
getExecutablePath = return "a.jsexe"
#else
{-# LINE 51 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
import Control.Exception (catch, throw)
import Foreign.C
import Foreign.Marshal.Alloc
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable
import System.IO.Error (isDoesNotExistError)
import System.Posix.Internals
{-# LINE 78 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
getExecutablePath :: IO FilePath
executablePath :: Maybe (IO (Maybe FilePath))
{-# LINE 207 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
foreign import ccall unsafe "sysctl"
c_sysctl
:: Ptr CInt
-> CUInt
-> Ptr CChar
-> Ptr CSize
-> Ptr CChar
-> CSize
-> IO CInt
getExecutablePath :: IO FilePath
getExecutablePath = do
[CInt] -> (Int -> Ptr CInt -> IO FilePath) -> IO FilePath
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CInt]
mib ((Int -> Ptr CInt -> IO FilePath) -> IO FilePath)
-> (Int -> Ptr CInt -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \Int
n Ptr CInt
mibPtr -> do
let mibLen :: CUInt
mibLen = Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
(Ptr CSize -> IO FilePath) -> IO FilePath
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO FilePath) -> IO FilePath)
-> (Ptr CSize -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
bufSizePtr -> do
CInt
status <- Ptr CInt
-> CUInt -> Ptr CChar -> Ptr CSize -> Ptr CChar -> CSize -> IO CInt
c_sysctl Ptr CInt
mibPtr CUInt
mibLen Ptr CChar
forall a. Ptr a
nullPtr Ptr CSize
bufSizePtr Ptr CChar
forall a. Ptr a
nullPtr CSize
0
case CInt
status of
CInt
0 -> do
Int
reqBufSize <- CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
bufSizePtr
Int -> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
reqBufSize ((Ptr CChar -> IO FilePath) -> IO FilePath)
-> (Ptr CChar -> IO FilePath) -> IO FilePath
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
buf -> do
CInt
newStatus <- Ptr CInt
-> CUInt -> Ptr CChar -> Ptr CSize -> Ptr CChar -> CSize -> IO CInt
c_sysctl Ptr CInt
mibPtr CUInt
mibLen Ptr CChar
buf Ptr CSize
bufSizePtr Ptr CChar
forall a. Ptr a
nullPtr CSize
0
case CInt
newStatus of
CInt
0 -> Ptr CChar -> IO FilePath
peekFilePath Ptr CChar
buf
CInt
_ -> IO FilePath
forall {a}. IO a
barf
CInt
_ -> IO FilePath
forall {a}. IO a
barf
where
barf :: IO a
barf = FilePath -> IO a
forall a. FilePath -> IO a
throwErrno FilePath
"getExecutablePath"
mib :: [CInt]
mib =
{-# LINE 236 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
[ (1)
{-# LINE 237 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
, (14)
{-# LINE 238 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
, (12)
{-# LINE 239 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
, -1
]
{-# LINE 248 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
executablePath :: Maybe (IO (Maybe FilePath))
executablePath = IO (Maybe FilePath) -> Maybe (IO (Maybe FilePath))
forall a. a -> Maybe a
Just ((FilePath -> Maybe FilePath) -> IO FilePath -> IO (Maybe FilePath)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just IO FilePath
getExecutablePath IO (Maybe FilePath)
-> (IOError -> IO (Maybe FilePath)) -> IO (Maybe FilePath)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` IOError -> IO (Maybe FilePath)
forall {f :: * -> *} {a}. Applicative f => IOError -> f (Maybe a)
f)
where
f :: IOError -> f (Maybe a)
f IOError
e | IOError -> Bool
isDoesNotExistError IOError
e = Maybe a -> f (Maybe a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = IOError -> f (Maybe a)
forall a e. Exception e => e -> a
throw IOError
e
{-# LINE 384 "libraries/base/System/Environment/ExecutablePath.hsc" #-}
#endif