Skip to content

Commit 2070f3d

Browse files
committed
Implement getSearchPath
1 parent a31bf53 commit 2070f3d

File tree

2 files changed

+171
-1
lines changed

2 files changed

+171
-1
lines changed

System/FilePath/Internal.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -268,7 +268,6 @@ splitSearchPath = f
268268
| otherwise -> [x]
269269

270270

271-
-- TODO for AFPP
272271
#ifndef OS_PATH
273272
-- | Get a list of 'FILEPATH's in the $PATH variable.
274273
getSearchPath :: IO [FILEPATH]

System/OsPath/Common.hs

Lines changed: 171 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE TypeApplications #-}
2+
{-# LANGUAGE PackageImports #-}
23
-- This template expects CPP definitions for:
34
--
45
-- WINDOWS defined? = no | yes | no
@@ -18,6 +19,19 @@
1819
#define POSIX_DOC
1920
#endif
2021

22+
#ifdef mingw32_HOST_OS
23+
#ifndef __WINDOWS_CCONV_H
24+
#define __WINDOWS_CCONV_H
25+
#if defined(i386_HOST_ARCH)
26+
# define WINDOWS_CCONV stdcall
27+
#elif defined(x86_64_HOST_ARCH)
28+
# define WINDOWS_CCONV ccall
29+
#else
30+
# error Unknown mingw32 arch
31+
#endif
32+
#endif
33+
#endif
34+
2135
#ifdef WINDOWS
2236
module System.OsPath.Windows
2337
#elif defined(POSIX)
@@ -75,6 +89,10 @@ module System.OsPath
7589

7690
-- * $PATH methods
7791
, splitSearchPath,
92+
#if defined(WINDOWS) || defined(POSIX)
93+
#else
94+
getSearchPath,
95+
#endif
7896

7997
-- * Extension functions
8098
splitExtension,
@@ -173,8 +191,27 @@ import System.OsString ( unsafeFromChar, toChar )
173191

174192
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
175193
import qualified System.OsPath.Windows as C
194+
import Control.Exception (throwIO, try)
195+
import Data.Char (isSpace)
196+
import Data.Bifunctor ( first )
197+
import Data.Word (Word32, Word8)
198+
import Foreign.C.Error (errnoToIOError, Errno(..))
199+
import Foreign.C.String (peekCWString)
200+
import Foreign.C.Types (CWchar, CInt(..))
201+
import Foreign.Ptr (nullPtr, Ptr)
202+
import GHC.IO.Exception
203+
import GHC.Ptr (castPtr)
204+
import Numeric (showHex)
205+
import System.IO.Error (ioeSetErrorString)
206+
import qualified "os-string" System.OsString.Data.ByteString.Short as B
207+
import "os-string" System.OsString.Data.ByteString.Short.Word16 (useAsCWString, useAsCWStringLen, packCWStringLen)
176208
#else
177209
import qualified System.OsPath.Posix as C
210+
import GHC.IO.Exception
211+
import Control.Exception (try)
212+
import Foreign
213+
import Foreign.C
214+
import qualified "os-string" System.OsString.Data.ByteString.Short as B
178215
#endif
179216

180217
import Data.Bifunctor
@@ -1467,3 +1504,137 @@ decodeFS (OsString (PosixString x)) = decodeWithBasePosix x
14671504

14681505
#endif
14691506

1507+
#ifdef WINDOWS
1508+
#elif defined(POSIX)
1509+
#else
1510+
1511+
-- | Get a list of 'FILEPATH's in the $PATH variable.
1512+
getSearchPath :: IO [OsPath]
1513+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
1514+
getSearchPath = do
1515+
path <- getEnv name >>= maybe handleError return
1516+
pure $ splitSearchPath (OsString path)
1517+
where
1518+
name = C.unsafeEncodeUtf "PATH"
1519+
handleError = do
1520+
err <- getLastError
1521+
if err == eERROR_ENVVAR_NOT_FOUND
1522+
then ioe_missingEnvVar name
1523+
else failWith "getSearchPath" err
1524+
1525+
eERROR_ENVVAR_NOT_FOUND :: DWORD
1526+
eERROR_ENVVAR_NOT_FOUND = 203
1527+
1528+
ioe_missingEnvVar :: C.WindowsString -> IO a
1529+
ioe_missingEnvVar name = do
1530+
name' <- either (const (fmap C.toChar . C.unpack $ name)) id <$> try @IOException (C.decodeFS name)
1531+
ioException (IOError Nothing NoSuchThing "getSearchPath"
1532+
"no environment variable" Nothing (Just name'))
1533+
1534+
failWith :: String -> ErrCode -> IO a
1535+
failWith fn_name err_code = do
1536+
c_msg <- getErrorMessage err_code
1537+
msg <- if c_msg == nullPtr
1538+
then return $ "Error 0x" ++ Numeric.showHex err_code ""
1539+
else do msg <- peekCWString c_msg
1540+
-- We ignore failure of freeing c_msg, given we're already failing
1541+
_ <- localFree c_msg
1542+
return msg
1543+
-- turn GetLastError() into errno, which errnoToIOError knows how to convert
1544+
-- to an IOException we can throw.
1545+
errno <- c_maperrno_func err_code
1546+
let msg' = reverse $ dropWhile isSpace $ reverse msg -- drop trailing \n
1547+
ioerror = errnoToIOError fn_name errno Nothing Nothing
1548+
`ioeSetErrorString` msg'
1549+
throwIO ioerror
1550+
1551+
errorWin :: String -> IO a
1552+
errorWin fn_name = do
1553+
err_code <- getLastError
1554+
failWith fn_name err_code
1555+
1556+
foreign import WINDOWS_CCONV unsafe "windows.h LocalFree"
1557+
localFree :: Ptr a -> IO (Ptr a)
1558+
1559+
foreign import ccall unsafe "errors.h"
1560+
getErrorMessage :: DWORD -> IO LPWSTR
1561+
1562+
foreign import ccall unsafe "maperrno_func"
1563+
c_maperrno_func :: ErrCode -> IO Errno
1564+
1565+
getEnv :: C.WindowsString -> IO (Maybe C.WindowsString)
1566+
getEnv name =
1567+
withTString name $ \c_name -> withTStringBufferLen maxLength $ \(buf, len) -> do
1568+
let c_len = fromIntegral len
1569+
c_len' <- c_GetEnvironmentVariableW c_name buf c_len
1570+
case c_len' of
1571+
0 -> do
1572+
err_code <- getLastError
1573+
if err_code == eERROR_ENVVAR_NOT_FOUND
1574+
then return Nothing
1575+
else errorWin "GetEnvironmentVariableW"
1576+
_ | c_len' > fromIntegral maxLength ->
1577+
ioError (IOError Nothing OtherError "GetEnvironmentVariableW" ("Unexpected return code: " <> show c_len') Nothing Nothing)
1578+
| otherwise -> do
1579+
let len' = fromIntegral c_len'
1580+
Just <$> peekTStringLen (buf, len')
1581+
where
1582+
maxLength :: Int
1583+
maxLength = 65535
1584+
1585+
foreign import WINDOWS_CCONV unsafe "windows.h GetLastError"
1586+
getLastError :: IO ErrCode
1587+
1588+
foreign import WINDOWS_CCONV unsafe "processenv.h GetEnvironmentVariableW"
1589+
c_GetEnvironmentVariableW :: LPCWSTR -> LPWSTR -> DWORD -> IO DWORD
1590+
1591+
withTStringBufferLen :: Int -> ((LPTSTR, Int) -> IO a) -> IO a
1592+
withTStringBufferLen maxLength
1593+
= let dummyBuffer = WindowsString $ B.pack $ replicate (if even maxLength then maxLength else maxLength + 1) _nul
1594+
in withTStringLen dummyBuffer
1595+
1596+
_nul :: Word8
1597+
_nul = 0x00
1598+
1599+
withTString :: C.WindowsString -> (LPTSTR -> IO a) -> IO a
1600+
withTString (WindowsString str) f = useAsCWString str (\ptr -> f (castPtr ptr))
1601+
1602+
withTStringLen :: C.WindowsString -> ((LPTSTR, Int) -> IO a) -> IO a
1603+
withTStringLen (WindowsString str) f = useAsCWStringLen str (\(ptr, len) -> f (castPtr ptr, len))
1604+
1605+
peekTStringLen :: (LPCTSTR, Int) -> IO C.WindowsString
1606+
peekTStringLen = fmap WindowsString . packCWStringLen . first castPtr
1607+
1608+
type DWORD = Word32
1609+
type ErrCode = DWORD
1610+
type LPWSTR = Ptr CWchar
1611+
type LPCWSTR = LPWSTR
1612+
type LPTSTR = Ptr TCHAR
1613+
type LPCTSTR = LPTSTR
1614+
type TCHAR = CWchar
1615+
1616+
#else
1617+
getSearchPath = do
1618+
path <- getEnv name >>= maybe (ioe_missingEnvVar name) return
1619+
pure $ splitSearchPath (OsString path)
1620+
where
1621+
name = C.unsafeEncodeUtf "PATH"
1622+
1623+
ioe_missingEnvVar :: C.PosixPath -> IO a
1624+
ioe_missingEnvVar name = do
1625+
name' <- either (const (fmap C.toChar . C.unpack $ name)) id <$> try @IOException (C.decodeFS name)
1626+
ioException (IOError Nothing NoSuchThing "getSearchPath"
1627+
"no environment variable" Nothing (Just name'))
1628+
1629+
getEnv :: PosixString -> IO (Maybe PosixString)
1630+
getEnv (PS name) = do
1631+
litstring <- B.useAsCString name c_getenv
1632+
if litstring /= nullPtr
1633+
then (Just . PS) <$> B.packCString litstring
1634+
else return Nothing
1635+
1636+
foreign import ccall unsafe "getenv"
1637+
c_getenv :: CString -> IO CString
1638+
#endif
1639+
1640+
#endif

0 commit comments

Comments
 (0)