Skip to content

Commit

Permalink
Replace "Array Word8" in the Event module with "Path" in Windows
Browse files Browse the repository at this point in the history
  • Loading branch information
adithyaov committed Oct 16, 2024
1 parent 6dbc4db commit 1b6234e
Showing 1 changed file with 19 additions and 29 deletions.
48 changes: 19 additions & 29 deletions src/Streamly/Internal/FileSystem/Event/Windows.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,15 +120,13 @@ import System.Win32.Types (BOOL, DWORD, HANDLE, LPVOID, LPDWORD, failIfFalse_)
import Streamly.Data.Array (Array)
import Streamly.Data.Stream (Stream)
import Streamly.Data.Stream.Prelude (eager)
import Streamly.Internal.FileSystem.Path (Path)

import qualified Data.List.NonEmpty as NonEmpty
import qualified Streamly.Data.Array as A (fromList)
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.Data.Stream as S
import qualified Streamly.Data.Stream.Prelude as S
import qualified Streamly.Unicode.Stream as U
import qualified Streamly.Internal.Unicode.Utf8 as UTF8 (pack, toArray)
import qualified Streamly.Internal.Data.Array as A (read)
import qualified Streamly.Internal.FileSystem.Path as Path

-- | Watch configuration, used to specify the events of interest and the
-- behavior of the watch.
Expand Down Expand Up @@ -428,12 +426,6 @@ pathsToHandles paths cfg = do
-- Utilities
-------------------------------------------------------------------------------

utf8ToString :: Array Word8 -> FilePath
utf8ToString = runIdentity . S.fold Fold.toList . U.decodeUtf8 . A.read

utf8ToStringList :: NonEmpty (Array Word8) -> NonEmpty FilePath
utf8ToStringList = NonEmpty.map utf8ToString

-- | Close a Directory handle.
--
closePathHandleStream :: Stream IO (HANDLE, FilePath, Config) -> IO ()
Expand Down Expand Up @@ -472,13 +464,16 @@ closePathHandleStream =
--
-- /Pre-release/
--
watchWith :: (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith :: (Config -> Config) -> NonEmpty Path -> Stream IO Event
watchWith f paths =
S.bracketIO before after (S.parConcatMap (eager True) eventStreamAggr)

where

before = return $ pathsToHandles (utf8ToStringList paths) $ f defaultConfig
before =
return
$ pathsToHandles (NonEmpty.map Path.toString paths)
$ f defaultConfig
after = closePathHandleStream

-- | Same as 'watchWith' using 'defaultConfig' and recursive mode.
Expand All @@ -487,7 +482,7 @@ watchWith f paths =
--
-- /Pre-release/
--
watchRecursive :: NonEmpty (Array Word8) -> Stream IO Event
watchRecursive :: NonEmpty Path -> Stream IO Event
watchRecursive = watchWith (setRecursiveMode True)

-- | Same as 'watchWith' using defaultConfig and non-recursive mode.
Expand All @@ -496,30 +491,26 @@ watchRecursive = watchWith (setRecursiveMode True)
--
-- /Pre-release/
--
watch :: NonEmpty (Array Word8) -> Stream IO Event
watch :: NonEmpty Path -> Stream IO Event
watch = watchWith id

getFlag :: DWORD -> Event -> Bool
getFlag mask Event{..} = eventFlags == mask

-- XXX Change the type to Array Word8 to make it compatible with other APIs.
--
-- | Get the file system object path for which the event is generated, relative
-- to the watched root. The path is a UTF-8 encoded array of bytes.
-- to the watched root.
--
-- /Pre-release/
--
getRelPath :: Event -> Array Word8
getRelPath Event{..} = (UTF8.toArray . UTF8.pack) eventRelPath
getRelPath :: Event -> Path
getRelPath Event{..} = Path.fromString eventRelPath

-- XXX Change the type to Array Word8 to make it compatible with other APIs.
--
-- | Get the watch root directory to which this event belongs.
--
-- /Pre-release/
--
getRoot :: Event -> Array Word8
getRoot Event{..} = (UTF8.toArray . UTF8.pack) eventRootPath
getRoot :: Event -> Path
getRoot Event{..} = Path.fromString eventRootPath

-- | Get the absolute file system object path for which the event is generated.
--
Expand All @@ -528,9 +519,8 @@ getRoot Event{..} = (UTF8.toArray . UTF8.pack) eventRootPath
--
-- /Pre-release/
--
getAbsPath :: Event -> Array Word8
getAbsPath ev = getRoot ev <> backSlash <> getRelPath ev
where backSlash = A.fromList [ fromIntegral (ord '\\') ]
getAbsPath :: Event -> Path
getAbsPath ev = Path.append (getRoot ev) (getRelPath ev)

-- XXX need to document the exact semantics of these.
--
Expand Down Expand Up @@ -625,9 +615,9 @@ isEventsLost Event{..} = totalBytes == 0
showEvent :: Event -> String
showEvent ev@Event{..} =
"--------------------------"
++ "\nRoot = " ++ utf8ToString (getRoot ev)
++ "\nPath = " ++ utf8ToString (getRelPath ev)
++ "\ngetAbsPath = " ++ utf8ToString (getAbsPath ev)
++ "\nRoot = " ++ Path.toString (getRoot ev)
++ "\nPath = " ++ Path.toString (getRelPath ev)
++ "\ngetAbsPath = " ++ Path.toString (getAbsPath ev)
++ "\nFlags " ++ show eventFlags
++ showev isEventsLost "Overflow"
++ showev isCreated "Created"
Expand Down

0 comments on commit 1b6234e

Please sign in to comment.