@@ -19,8 +19,8 @@ module Streamly.Internal.FileSystem.Path.Common
1919 , validateFile
2020
2121 -- * Construction
22- , fromChunk
23- , unsafeFromChunk
22+ , fromArray
23+ , unsafeFromArray
2424 , fromChars
2525 , unsafeFromChars
2626
@@ -35,6 +35,7 @@ module Streamly.Internal.FileSystem.Path.Common
3535 , primarySeparator
3636 , isSeparator
3737 , dropTrailingSeparators
38+ , dropTrailingBy
3839 , hasTrailingSeparator
3940 , hasLeadingSeparator
4041
@@ -85,7 +86,7 @@ module Streamly.Internal.FileSystem.Path.Common
8586 , normalizeSeparators
8687 -- , normalize -- separators and /./ components (split/combine)
8788 , eqPathBytes
88- , EqCfg
89+ , EqCfg ( .. )
8990 , ignoreTrailingSeparators
9091 , ignoreCase
9192 , allowRelativeEquality
@@ -165,6 +166,10 @@ data OS = Windows | Posix deriving Eq
165166-- XXX We can use Enum type class to include the Char type as well so that the
166167-- functions can work on Array Word8/Word16/Char but that may be slow.
167168
169+ -- XXX Windows is supported only on little endian machines so generally we do
170+ -- not need covnersion from LE to BE format unless we want to manipulate
171+ -- windows paths on big-endian machines.
172+
168173-- | Unsafe, may tructate to shorter word types, can only be used safely for
169174-- characters that fit in the given word size.
170175charToWord :: Integral a => Char -> a
@@ -235,6 +240,9 @@ isSeparatorWord os = isSeparator os . wordToChar
235240-- @a@. On Windows "c:" and "c:/" are different paths, therefore, we do not
236241-- drop the trailing separator from "c:/" or for that matter a separator
237242-- preceded by a ':'.
243+ --
244+ -- Can't use any arbitrary predicate "p", the logic in this depends on assuming
245+ -- that it is a path separator.
238246{-# INLINE dropTrailingBy #-}
239247dropTrailingBy :: (Unbox a , Integral a ) =>
240248 OS -> (a -> Bool ) -> Array a -> Array a
@@ -245,13 +253,23 @@ dropTrailingBy os p arr =
245253 in if n == 0
246254 then arr
247255 else if n == len -- "////"
248- then fst $ Array. unsafeBreakAt 1 arr
249- -- "c:////"
256+ then
257+ -- Even though "//" is not allowed as a valid path.
258+ -- We still handle that case in this low level function.
259+ if os == Windows
260+ && n >= 2
261+ && Array. unsafeGetIndex 0 arr == Array. unsafeGetIndex 1 arr
262+ then fst $ Array. unsafeBreakAt 2 arr -- make it "//" share name
263+ else fst $ Array. unsafeBreakAt 1 arr
264+ -- "c:////" - keep one "/" after colon in ".*:///" otherwise it will
265+ -- change the meaning. "c:/" may also appear, in the middle e.g.
266+ -- in UNC paths.
250267 else if (os == Windows )
251268 && (Array. unsafeGetIndex (len - n - 1 ) arr == charToWord ' :' )
252269 then fst $ Array. unsafeBreakAt (len - n + 1 ) arr
253270 else arr1
254271
272+ -- XXX we cannot compact "//" to "/" on windows
255273{-# INLINE compactTrailingBy #-}
256274compactTrailingBy :: Unbox a => (a -> Bool ) -> Array a -> Array a
257275compactTrailingBy p arr =
@@ -1158,8 +1176,9 @@ validatePathWith allowRoot Windows path
11581176validatePath :: (MonadThrow m , Integral a , Unbox a ) => OS -> Array a -> m ()
11591177validatePath = validatePathWith True
11601178
1161- -- | Like validatePath but on Windows only full paths are allowed, path roots
1162- -- only are not allowed. Thus "//x/" is not valid.
1179+ -- | Like validatePath but on Windows the path must refer to a file system
1180+ -- object, share roots or prefixes not referring to a specific path are not
1181+ -- allowed. Thus "//x/" is not a valid path.
11631182{-# INLINE validatePath' #-}
11641183validatePath' :: (MonadThrow m , Integral a , Unbox a ) => OS -> Array a -> m ()
11651184validatePath' = validatePathWith False
@@ -1187,18 +1206,18 @@ isValidPath' os path =
11871206 Nothing -> False
11881207 Just _ -> True
11891208
1190- {-# INLINE unsafeFromChunk #-}
1191- unsafeFromChunk :: Array a -> Array a
1192- unsafeFromChunk = id
1209+ {-# INLINE unsafeFromArray #-}
1210+ unsafeFromArray :: Array a -> Array a
1211+ unsafeFromArray = id
11931212
1194- {-# INLINE fromChunk #-}
1195- fromChunk :: forall m a . (MonadThrow m , Unbox a , Integral a ) =>
1213+ {-# INLINE fromArray #-}
1214+ fromArray :: forall m a . (MonadThrow m , Unbox a , Integral a ) =>
11961215 OS -> Array a -> m (Array a )
1197- fromChunk os arr = validatePath os arr >> pure arr
1216+ fromArray os arr = validatePath os arr >> pure arr
11981217{-
11991218 let arr1 = Array.unsafeCast arr :: Array a
12001219 in validatePath os arr1 >> pure arr1
1201- fromChunk Windows arr =
1220+ fromArray Windows arr =
12021221 case Array.cast arr of
12031222 Nothing ->
12041223 throwM
@@ -1228,7 +1247,7 @@ fromChars :: (MonadThrow m, Unbox a, Integral a) =>
12281247 -> m (Array a )
12291248fromChars os encode s =
12301249 let arr = unsafeFromChars encode s
1231- in fromChunk os (Array. unsafeCast arr)
1250+ in fromArray os (Array. unsafeCast arr)
12321251
12331252{-# INLINE toChars #-}
12341253toChars :: (Monad m , Unbox a ) =>
@@ -1392,6 +1411,7 @@ eqPathBytes = Array.byteEq
13921411-- control the strictness.
13931412--
13941413-- The default configuration is as follows:
1414+ --
13951415-- >>> :{
13961416-- defaultMod = ignoreTrailingSeparators False
13971417-- . ignoreCase False
@@ -1411,33 +1431,36 @@ data EqCfg =
14111431 -- , noIgnoreRedundantDot -- "x\/.\/" \/= "x"
14121432 }
14131433
1414- -- | Default equality check configuration.
1415- --
1416- -- > :{
1417- -- > eqCfg = EqCfg
1418- -- > { ignoreTrailingSeparators = False
1419- -- > , ignoreCase = False
1420- -- > , allowRelativeEquality = False
1421- -- > }
1422- -- > :}
1423- --
1424- eqCfg :: EqCfg
1425- eqCfg = EqCfg
1426- { _ignoreTrailingSeparators = False
1427- , _ignoreCase = False
1428- , _allowRelativeEquality = False
1429- }
1430-
1434+ -- | When set to 'False', a path with a trailing slash and a path without are
1435+ -- treated as unequal e.g. "x" is not the same as "x\/". The latter is a
1436+ -- directory.
1437+ --
1438+ -- /Default/: False
14311439ignoreTrailingSeparators :: Bool -> EqCfg -> EqCfg
14321440ignoreTrailingSeparators val conf = conf { _ignoreTrailingSeparators = val }
14331441
1442+ -- | When set to 'False', comparison is case sensitive.
1443+ --
1444+ -- /Posix Default/: False
1445+ --
1446+ -- /Windows Default/: True
14341447ignoreCase :: Bool -> EqCfg -> EqCfg
14351448ignoreCase val conf = conf { _ignoreCase = val }
14361449
1450+ -- | When set to 'False':
1451+ --
1452+ -- * paths with a leading "." and without a leading "." e.g. ".\/x\/y" and
1453+ -- "x\/y" are treated as unequal. The first one is a dynamically rooted path
1454+ -- and the second one is a branch or free path segment.
1455+ --
1456+ -- * Two paths starting with a leading "." may not actually be equal even if
1457+ -- they are literally equal, depending on the meaning of ".". We return unequal
1458+ -- even though they may be equal sometimes.
1459+ --
1460+ -- /Default/: False
14371461allowRelativeEquality :: Bool -> EqCfg -> EqCfg
14381462allowRelativeEquality val conf = conf { _allowRelativeEquality = val }
14391463
1440-
14411464data PosixRoot = PosixRootAbs | PosixRootRel deriving Eq
14421465
14431466data WindowsRoot =
@@ -1547,8 +1570,8 @@ eqComponentsWith ignCase decoder os a b =
15471570{-# INLINE eqPath #-}
15481571eqPath :: (Unbox a , Integral a ) =>
15491572 (Stream Identity a -> Stream Identity Char )
1550- -> OS -> ( EqCfg -> EqCfg ) -> Array a -> Array a -> Bool
1551- eqPath decoder os configMod a b =
1573+ -> OS -> EqCfg -> Array a -> Array a -> Bool
1574+ eqPath decoder os EqCfg { .. } a b =
15521575 let (rootA, stemA) = splitRoot os a
15531576 (rootB, stemB) = splitRoot os b
15541577
@@ -1570,5 +1593,3 @@ eqPath decoder os configMod a b =
15701593 eqRelative
15711594 && eqTrailingSep
15721595 && eqComponentsWith _ignoreCase decoder os stemA stemB
1573- where
1574- EqCfg {.. } = configMod eqCfg
0 commit comments