Skip to content

Commit ebdcce7

Browse files
Change fromChunk signature for Windows
This is to avoid inadvertant errors e.g. in readRaw we were reading it as a Word8 array on Windows even though we should be reading it as Word16.
1 parent 2eb801b commit ebdcce7

File tree

3 files changed

+37
-26
lines changed

3 files changed

+37
-26
lines changed

core/src/Streamly/Internal/FileSystem/Path/Common.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1185,15 +1185,16 @@ isValidPath' os path =
11851185
Just _ -> True
11861186

11871187
{-# INLINE unsafeFromChunk #-}
1188-
unsafeFromChunk :: Array Word8 -> Array a
1189-
unsafeFromChunk = Array.unsafeCast
1188+
unsafeFromChunk :: Array a -> Array a
1189+
unsafeFromChunk = id
11901190

11911191
{-# INLINE fromChunk #-}
11921192
fromChunk :: forall m a. (MonadThrow m, Unbox a, Integral a) =>
1193-
OS -> Array Word8 -> m (Array a)
1194-
fromChunk Posix arr =
1193+
OS -> Array a -> m (Array a)
1194+
fromChunk os arr = validatePath os arr >> pure arr
1195+
{-
11951196
let arr1 = Array.unsafeCast arr :: Array a
1196-
in validatePath Posix arr1 >> pure arr1
1197+
in validatePath os arr1 >> pure arr1
11971198
fromChunk Windows arr =
11981199
case Array.cast arr of
11991200
Nothing ->
@@ -1202,6 +1203,7 @@ fromChunk Windows arr =
12021203
$ "Encoded path length " ++ show (Array.byteLength arr)
12031204
++ " is not a multiple of 16-bit."
12041205
Just x -> validatePath Windows x >> pure x
1206+
-}
12051207

12061208
-- | Convert 'Path' to an array of bytes.
12071209
{-# INLINE toChunk #-}

core/src/Streamly/Internal/FileSystem/PosixPath.hs

Lines changed: 15 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -276,11 +276,15 @@ isValidPath a = Common.isValidPath Common.OS_NAME a
276276
-- been using it consistently in streamly. We use "bytes" for a stream of
277277
-- bytes.
278278

279-
-- | /Unsafe/: The user is responsible to make sure that the failure cases
280-
-- mentioned in 'fromChunk' cannot occur.
279+
-- | /Unsafe/: The user is responsible to make sure that the path is valid as
280+
-- per 'isValidPath'.
281281
--
282282
{-# INLINE unsafeFromChunk #-}
283+
#ifndef IS_WINDOWS
283284
unsafeFromChunk :: IsPath OS_PATH a => Array Word8 -> a
285+
#else
286+
unsafeFromChunk :: IsPath OS_PATH a => Array Word16 -> a
287+
#endif
284288
unsafeFromChunk =
285289
#ifndef DEBUG
286290
unsafeFromPath . OS_PATH . Common.unsafeFromChunk
@@ -290,13 +294,14 @@ unsafeFromChunk =
290294

291295
-- XXX mkPath?
292296

293-
-- | Convert a byte array into a Path:
294-
--
295-
-- * Throws 'InvalidPath' if 'isValidPath' fails on the path.
296-
-- * On Windows, throws 'InvalidPath' if the array length is not aligned on two
297-
-- byte boundary.
297+
-- | Convert a byte array into a Path.
298+
-- Throws 'InvalidPath' if 'isValidPath' fails on the path.
298299
--
300+
#ifndef IS_WINDOWS
299301
fromChunk :: (MonadThrow m, IsPath OS_PATH a) => Array Word8 -> m a
302+
#else
303+
fromChunk :: (MonadThrow m, IsPath OS_PATH a) => Array Word16 -> m a
304+
#endif
300305
fromChunk arr = Common.fromChunk Common.OS_NAME arr >>= fromPath . OS_PATH
301306

302307
-- XXX Should be a Fold instead?
@@ -423,27 +428,18 @@ showRaw p =
423428
toPath p in show arr
424429

425430
#ifndef IS_WINDOWS
426-
-- | Read a raw array as a path type.
431+
-- | Parse a raw array of bytes as a path type.
427432
--
428433
-- >>> readRaw = fromJust . Path.fromChunk . read
429434
--
430-
-- >>> arr <- Stream.fold Array.create $ Unicode.encodeUtf8 $ Stream.fromList "hello"
435+
-- >>> arr = rawFromString "hello"
431436
-- >>> Path.showRaw $ (Path.readRaw $ show arr :: Path.PosixPath)
432437
-- "fromList [104,101,108,108,111]"
433438
--
434439
-- See also: 'showRaw'.
435-
#else
436-
-- | Read a raw array as a path type.
437-
--
438-
-- >> readRaw = fromJust . Path.fromChunk . read
439-
--
440-
-- >> arr <- Stream.fold Array.create $ Unicode.encodeUtf16LE $ Stream.fromList "hello"
441-
-- >> Path.showRaw $ (Path.readRaw $ show arr :: Path.WindowsPath)
442-
--
443-
-- See also: 'showRaw'.
444-
#endif
445440
readRaw :: IsPath OS_PATH a => [Char] -> a
446441
readRaw = fromJust . fromChunk . read
442+
#endif
447443

448444
-- We cannot show decoded path in the Show instance as it may not always
449445
-- succeed and it depends on the encoding which we may not even know. The

core/src/Streamly/Internal/FileSystem/WindowsPath.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,19 +5,21 @@
55
>>> :m
66
>>> :set -XQuasiQuotes
77
>>> import Data.Maybe (fromJust)
8+
>>> import Data.Word (Word16)
89
>>> import qualified Streamly.Data.Stream as Stream
910
1011
For APIs that have not been released yet.
1112
1213
>>> import Streamly.Internal.FileSystem.WindowsPath (WindowsPath, path)
14+
>>> import Streamly.Internal.Data.Array (Array)
1315
>>> import qualified Streamly.Internal.Data.Array as Array
1416
>>> import qualified Streamly.Internal.FileSystem.WindowsPath as Path
1517
>>> import qualified Streamly.Internal.Unicode.Stream as Unicode
1618
1719
>>> import Data.Either (Either, isLeft)
1820
>>> import Control.Exception (SomeException, evaluate, try)
1921
20-
>>> rawFromString = Array.fromPureStream . Unicode.encodeUtf8' . Stream.fromList
22+
>>> rawFromString = Array.fromPureStream . Unicode.encodeUtf16le' . Stream.fromList
2123
>>> pack = fromJust . Path.fromString
2224
>>> fails action = (try (evaluate action) :: IO (Either SomeException String)) >>= return . isLeft
2325
-}
@@ -34,7 +36,6 @@ For APIs that have not been released yet.
3436
-- | Check if the filepath is valid i.e. does the operating system or the file
3537
-- system allow such a path in listing or creating files?
3638
--
37-
-- >>> rawFromString = Array.fromPureStream . Unicode.encodeUtf16le' . Stream.fromList
3839
-- >>> isValid = Path.isValidPath . rawFromString
3940
--
4041
-- >>> isValid ""
@@ -158,6 +159,18 @@ validatePath' a = Common.validatePath' Common.Windows a
158159
isValidPath' :: Array Word16 -> Bool
159160
isValidPath' a = Common.isValidPath' Common.Windows a
160161

162+
-- | Read a raw array of Word16 as a path type.
163+
--
164+
-- >>> readRaw = fromJust . Path.fromChunk . read
165+
--
166+
-- >>> arr :: Array Word16 = rawFromString "hello"
167+
-- >>> Path.showRaw $ (Path.readRaw $ show arr :: Path.WindowsPath)
168+
-- "fromList [104,101,108,108,111]"
169+
--
170+
-- See also: 'showRaw'.
171+
readRaw :: IsPath OS_PATH a => [Char] -> a
172+
readRaw = fromJust . fromChunk . read
173+
161174
-- | A path that is attached to a root. "C:\\" is considered an absolute root
162175
-- and "." as a dynamic root. ".." is not considered a root, "..\/x" or "x\/y"
163176
-- are not rooted paths.

0 commit comments

Comments
 (0)