Merge remote-tracking branch 'origin/issue-766'
This commit is contained in:
commit
6d46849fec
@ -279,11 +279,11 @@ removeEmptyDirectory = PD.removeDirectory
|
|||||||
|
|
||||||
-- | Create an 'Unfold' of directory contents.
|
-- | Create an 'Unfold' of directory contents.
|
||||||
unfoldDirContents :: (MonadMask m, MonadIO m, S.MonadAsync m) => Unfold m FilePath (FD.DirType, FilePath)
|
unfoldDirContents :: (MonadMask m, MonadIO m, S.MonadAsync m) => Unfold m FilePath (FD.DirType, FilePath)
|
||||||
unfoldDirContents = U.bracket (liftIO . openDirStream) (liftIO . closeDirStream) (Unfold step return)
|
unfoldDirContents = U.bracket (liftIO . openDirStreamPortable) (liftIO . closeDirStreamPortable) (Unfold step return)
|
||||||
where
|
where
|
||||||
{-# INLINE [0] step #-}
|
{-# INLINE [0] step #-}
|
||||||
step dirstream = do
|
step dirstream = do
|
||||||
(typ, e) <- liftIO $ readDirEnt dirstream
|
(typ, e) <- liftIO $ readDirEntPortable dirstream
|
||||||
return $ if
|
return $ if
|
||||||
| null e -> D.Stop
|
| null e -> D.Stop
|
||||||
| "." == e -> D.Skip dirstream
|
| "." == e -> D.Skip dirstream
|
||||||
@ -308,8 +308,8 @@ getDirectoryContentsRecursiveUnfold = Unfold step (\s -> return (s, Nothing, [""
|
|||||||
step (_, Nothing, []) = return D.Stop
|
step (_, Nothing, []) = return D.Stop
|
||||||
|
|
||||||
step (topdir, Just (cdir, dirstream, finalizer), dirs) = flip onException (runIOFinalizer finalizer) $ do
|
step (topdir, Just (cdir, dirstream, finalizer), dirs) = flip onException (runIOFinalizer finalizer) $ do
|
||||||
(dt, f) <- liftIO $ readDirEnt dirstream
|
(dt, f) <- liftIO $ readDirEntPortable dirstream
|
||||||
if | FD.dtUnknown == dt -> do
|
if | f == "" -> do
|
||||||
runIOFinalizer finalizer
|
runIOFinalizer finalizer
|
||||||
return $ D.Skip (topdir, Nothing, dirs)
|
return $ D.Skip (topdir, Nothing, dirs)
|
||||||
| f == "." || f == ".."
|
| f == "." || f == ".."
|
||||||
@ -323,8 +323,8 @@ getDirectoryContentsRecursiveUnfold = Unfold step (\s -> return (s, Nothing, [""
|
|||||||
|
|
||||||
acquire dir =
|
acquire dir =
|
||||||
withRunInIO $ \run -> mask_ $ run $ do
|
withRunInIO $ \run -> mask_ $ run $ do
|
||||||
dirstream <- liftIO $ openDirStream dir
|
dirstream <- liftIO $ openDirStreamPortable dir
|
||||||
ref <- newIOFinalizer (liftIO $ closeDirStream dirstream)
|
ref <- newIOFinalizer (liftIO $ closeDirStreamPortable dirstream)
|
||||||
return (dirstream, ref)
|
return (dirstream, ref)
|
||||||
|
|
||||||
getDirectoryContentsRecursiveBFSUnsafe :: (MonadMask m, MonadIO m, S.MonadAsync m)
|
getDirectoryContentsRecursiveBFSUnsafe :: (MonadMask m, MonadIO m, S.MonadAsync m)
|
||||||
|
@ -10,9 +10,20 @@
|
|||||||
module GHCup.Prelude.File.Posix.Traversals (
|
module GHCup.Prelude.File.Posix.Traversals (
|
||||||
-- lower-level stuff
|
-- lower-level stuff
|
||||||
readDirEnt
|
readDirEnt
|
||||||
|
, readDirEntPortable
|
||||||
|
, openDirStreamPortable
|
||||||
|
, closeDirStreamPortable
|
||||||
, unpackDirStream
|
, unpackDirStream
|
||||||
|
, DirStreamPortable
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
#include <limits.h>
|
||||||
|
#include <stdlib.h>
|
||||||
|
#include <dirent.h>
|
||||||
|
#include <sys/types.h>
|
||||||
|
#include <sys/stat.h>
|
||||||
|
#include <fcntl.h>
|
||||||
|
|
||||||
|
|
||||||
#if __GLASGOW_HASKELL__ < 710
|
#if __GLASGOW_HASKELL__ < 710
|
||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
@ -28,6 +39,7 @@ import Foreign.Storable
|
|||||||
import System.Posix
|
import System.Posix
|
||||||
import Foreign (alloca)
|
import Foreign (alloca)
|
||||||
import System.Posix.Internals (peekFilePath)
|
import System.Posix.Internals (peekFilePath)
|
||||||
|
import System.FilePath
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@ -90,3 +102,31 @@ readDirEnt (unpackDirStream -> dirp) =
|
|||||||
then return (dtUnknown, mempty)
|
then return (dtUnknown, mempty)
|
||||||
else throwErrno "readDirEnt"
|
else throwErrno "readDirEnt"
|
||||||
|
|
||||||
|
|
||||||
|
newtype DirStreamPortable = DirStreamPortable (FilePath, DirStream)
|
||||||
|
|
||||||
|
openDirStreamPortable :: FilePath -> IO DirStreamPortable
|
||||||
|
openDirStreamPortable fp = do
|
||||||
|
dirs <- openDirStream fp
|
||||||
|
pure $ DirStreamPortable (fp, dirs)
|
||||||
|
|
||||||
|
closeDirStreamPortable :: DirStreamPortable -> IO ()
|
||||||
|
closeDirStreamPortable (DirStreamPortable (_, dirs)) = closeDirStream dirs
|
||||||
|
|
||||||
|
readDirEntPortable :: DirStreamPortable -> IO (DirType, FilePath)
|
||||||
|
readDirEntPortable (DirStreamPortable (basedir, dirs)) = do
|
||||||
|
(dt, fp) <- readDirEnt dirs
|
||||||
|
case (dt, fp) of
|
||||||
|
(DirType #{const DT_UNKNOWN}, _)
|
||||||
|
| fp /= "" -> do
|
||||||
|
stat <- getSymbolicLinkStatus (basedir </> fp)
|
||||||
|
pure $ (, fp) $ if | isBlockDevice stat -> DirType #{const DT_BLK}
|
||||||
|
| isCharacterDevice stat -> DirType #{const DT_CHR}
|
||||||
|
| isDirectory stat -> DirType #{const DT_DIR}
|
||||||
|
| isNamedPipe stat -> DirType #{const DT_FIFO}
|
||||||
|
| isSymbolicLink stat -> DirType #{const DT_LNK}
|
||||||
|
| isRegularFile stat -> DirType #{const DT_REG}
|
||||||
|
| isSocket stat -> DirType #{const DT_SOCK}
|
||||||
|
| otherwise -> DirType #{const DT_UNKNOWN}
|
||||||
|
_ -> pure (dt, fp)
|
||||||
|
|
@ -24,11 +24,11 @@ spec = do
|
|||||||
-- https://github.com/haskell/ghcup-hs/issues/415
|
-- https://github.com/haskell/ghcup-hs/issues/415
|
||||||
describe "GHCup.Prelude.File.Posix.Traversals" $ do
|
describe "GHCup.Prelude.File.Posix.Traversals" $ do
|
||||||
it "readDirEnt" $ do
|
it "readDirEnt" $ do
|
||||||
dirstream <- liftIO $ openDirStream "test/data"
|
dirstream <- liftIO $ openDirStreamPortable "test/data"
|
||||||
(dt1, fp1) <- readDirEnt dirstream
|
(dt1, fp1) <- readDirEntPortable dirstream
|
||||||
(dt2, fp2) <- readDirEnt dirstream
|
(dt2, fp2) <- readDirEntPortable dirstream
|
||||||
(dt3, fp3) <- readDirEnt dirstream
|
(dt3, fp3) <- readDirEntPortable dirstream
|
||||||
(dt4, fp4) <- readDirEnt dirstream
|
(dt4, fp4) <- readDirEntPortable dirstream
|
||||||
let xs = sortOn snd [ (dt1, fp1), (dt2, fp2)
|
let xs = sortOn snd [ (dt1, fp1), (dt2, fp2)
|
||||||
, (dt3, fp3), (dt4, fp4)
|
, (dt3, fp3), (dt4, fp4)
|
||||||
]
|
]
|
||||||
|
Loading…
Reference in New Issue
Block a user