{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module System.Directory.OsPath.Streaming
( DirStream
, openDirStream
, readDirStream
, closeDirStream
) where
import System.OsPath (osp)
#ifdef mingw32_HOST_OS
import Control.Concurrent.Counter (Counter)
import Control.Concurrent.Counter qualified as Counter
import Control.Monad (unless)
import System.OsPath.Types (OsPath)
import System.OsString.Internal.Types (OsString(OsString), getOsString)
import System.OsString.Windows (pstr)
import System.Win32.Types qualified as Win32
import System.Win32.WindowsString.File qualified as Win32
data DirStream = DirStream !Win32.HANDLE !Win32.FindData !Counter
openDirStream :: OsPath -> IO DirStream
openDirStream fp = do
(h, fdat) <- Win32.findFirstFile $ getOsString fp <> [pstr|\*|]
hasMore <- Counter.new 1
pure $! DirStream h fdat hasMore
closeDirStream :: DirStream -> IO ()
closeDirStream (DirStream h _ _) = Win32.findClose h
readDirStream :: DirStream -> IO (Maybe OsPath)
readDirStream (DirStream h fdat hasMore) = go
where
go = do
hasMore' <- Counter.get hasMore
if hasMore' /= 0
then do
filename <- Win32.getFindDataFileName fdat
hasMore'' <- Win32.findNextFile h fdat
unless hasMore'' $
Counter.set hasMore 0
if filename == getOsString [osp|.|] || filename == getOsString [osp|..|]
then go
else pure $ Just $ OsString filename
else pure Nothing
#else
import System.OsPath.Types (OsPath)
import System.OsString.Internal.Types (OsString(OsString), getOsString)
import System.Posix.Directory.PosixPath (DirStream, closeDirStream)
import System.Posix.Directory.PosixPath qualified as Posix
openDirStream :: OsPath -> IO DirStream
openDirStream :: OsPath -> IO DirStream
openDirStream = PosixPath -> IO DirStream
Posix.openDirStream forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> PosixPath
getOsString
{-# INLINE readDirStream #-}
readDirStream :: DirStream -> IO (Maybe OsPath)
readDirStream :: DirStream -> IO (Maybe OsPath)
readDirStream DirStream
ds = IO (Maybe OsPath)
go
where
go :: IO (Maybe OsPath)
go = do
PosixPath
fp <- DirStream -> IO PosixPath
Posix.readDirStream DirStream
ds
case () of
()
_ | PosixPath
fp forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty
-> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
| PosixPath
fp forall a. Eq a => a -> a -> Bool
== OsPath -> PosixPath
getOsString [osp|.|] Bool -> Bool -> Bool
|| PosixPath
fp forall a. Eq a => a -> a -> Bool
== OsPath -> PosixPath
getOsString [osp|..|]
-> IO (Maybe OsPath)
go
| Bool
otherwise
-> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ PosixPath -> OsPath
OsString PosixPath
fp
#endif