{-# language BangPatterns #-}
{-# language MagicHash #-}
{-# language LambdaCase #-}
{-# language UnboxedTuples #-}
module Posix.Directory
( getCurrentWorkingDirectory
) where
import Data.Primitive (Addr(..),ByteArray)
import GHC.Exts (Ptr(..))
import Foreign.Ptr (nullPtr)
import Foreign.C.Error (Errno,eRANGE,getErrno)
import Foreign.C.Types (CChar,CSize(..))
import GHC.IO (IO(..))
import qualified Data.Primitive as PM
import qualified Foreign.Storable as FS
foreign import ccall safe "getcwd"
c_getcwd :: Ptr CChar -> CSize -> IO (Ptr CChar)
getCurrentWorkingDirectory :: IO (Either Errno ByteArray)
getCurrentWorkingDirectory = go (4096 - chunkOverhead) where
go !sz = do
marr <- PM.newPinnedByteArray sz
let !(Addr addr) = PM.mutableByteArrayContents marr
ptr <- c_getcwd (Ptr addr) (intToCSize sz)
if ptr /= nullPtr
then do
strSize <- findNullByte ptr
dst <- PM.newByteArray strSize
PM.copyMutableByteArray dst 0 marr 0 strSize
dst' <- PM.unsafeFreezeByteArray dst
pure (Right dst')
else do
errno <- getErrno
if errno == eRANGE
then go (2 * sz)
else fmap Left getErrno
chunkOverhead :: Int
chunkOverhead = 2 * PM.sizeOf (undefined :: Int)
intToCSize :: Int -> CSize
intToCSize = fromIntegral
findNullByte :: Ptr CChar -> IO Int
findNullByte = go 0 where
go :: Int -> Ptr CChar -> IO Int
go !ix !ptr = do
FS.peekElemOff ptr ix >>= \case
0 -> pure ix
_ -> go (ix + 1) ptr