3333-- path is that it maps the characters SEPARATORS and @.@ to WORD_TYPE
3434-- representing their ASCII values. Operations are provided to encode and
3535-- decode using CODEC_NAME encoding.
36+ --
37+ -- This module has APIs that are equivalent to or can emulate all or most of
38+ -- the filepath package APIs. It has some differences from the filepath
39+ -- package:
40+ --
41+ -- * The default Path type it self affords considerable safety regarding the
42+ -- distinction of rooted or non-rooted paths, it also allows distinguishing
43+ -- directory and file paths.
44+ -- * It is designed to provide flexible typing to provide compile time safety
45+ -- for rooted/non-rooted paths and file/dir paths. The Path type is just part
46+ -- of that typed path ecosystem. Though the default Path type itself should be
47+ -- enough for most cases.
48+ -- * It leverages the streamly array module for most of the heavy lifting,
49+ -- it is a thin wrapper on top of that, improving maintainability as well as
50+ -- providing better performance. We can have pinned and unpinned paths, also
51+ -- provide lower level operations for certain cases to interact more
52+ -- efficinetly with low level code.
3653
3754module Streamly.Internal.FileSystem.OS_PATH
3855 (
@@ -59,7 +76,7 @@ module Streamly.Internal.FileSystem.OS_PATH
5976 , rawFromString
6077 , unsafeFromString
6178 -- , fromCString#
62- -- , fromW16CString #
79+ -- , fromCWString #
6380 , readRaw
6481
6582 -- * Statically Verified String Literals
@@ -88,40 +105,60 @@ module Streamly.Internal.FileSystem.OS_PATH
88105 , toString_
89106 , showRaw
90107
91- -- * Separators
92- -- Do we need to export the separator functions? They are not essential if
93- -- operations to split and combine paths are provided. If someone wants to
94- -- work on paths at low level then they know what they are.
108+ -- -- * Separators
109+ -- Do we need to export the separator char functions? They are not
110+ -- essential if operations to split and combine paths are provided. If
111+ -- someone wants to work on paths at low level then they know what they
112+ -- are.
95113 -- , isPrimarySeparator
96114 -- , isSeparator
115+
116+ -- * Dir or non-dir paths
117+ --
118+ -- XXX These are unstable APIs. We may change them such that the trailing
119+ -- separators are not removed or added if the path is a root/drive.
120+ -- Therefore, the meaning of these would be just to change the directory
121+ -- status of the path, if any, and nothing else. We may want to change the
122+ -- names accordingly. Also see the Node module implementation for code
123+ -- reuse.
124+
97125 , dropTrailingSeparators
126+ , hasTrailingSeparator
127+ , addTrailingSeparator
98128
99- -- * Tests
129+ -- * Path Segment Types
100130 , isRooted
101131 , isBranch
102132
103133 -- * Joining
104- , unsafeAppend
105- , append
106- , append'
134+ , addString
135+ -- , concat
136+ , unsafeAppend -- XXX unsafeExtend
107137#ifndef IS_WINDOWS
108- , appendCString
138+ , appendCString -- XXX extendByCString
109139 , appendCString'
110140#endif
141+ , append -- XXX rename to "extend" to emphasize asymmetric nature?
142+ , append' -- XXX rename to extendDir, to avoid pinned confusion?
143+ , unsafeJoinPaths
111144
112145 -- * Splitting
146+ -- | Note: you can use 'unsafeAppend' as a replacement for the joinDrive
147+ -- function in the filepath package.
113148 , splitRoot
114149 , splitPath
115150 , splitPath_
116151 , splitFile
117152 , splitExtension
153+ , addExtension
118154
119155 -- * Equality
120156 , eqPath
121157 , EqCfg (.. )
122158 , eqCfg
123159 , eqPathWith
124160 , eqPathBytes
161+ , normalize
125162 )
126163where
127164
@@ -223,23 +260,48 @@ adapt p = fromPath (toPath p :: OS_PATH)
223260-- Path parsing utilities
224261------------------------------------------------------------------------------
225262
226- -- | If the path is @//@ the result is @/@. If it is @dir//@ then the result is
227- -- @dir@. On Windows "c:" and "c:/" are different paths, therefore, we do not
228- -- drop the trailing separator from "c:/".
263+ -- | Drop all trailing separators from a path. This can potentially convert an
264+ -- implicit dir path to a non-dir.
229265--
230- -- Note that a path with trailing separators may implicitly be considered as a
231- -- directory by some applications. So dropping it may change the dir nature of
232- -- the path.
266+ -- Normally, if the path is @dir//@ then the result is @dir@; there are a few
267+ -- special cases though:
268+ --
269+ -- * If the path is @\/\/@ then the result is @\/@.
270+ -- * On Windows, if the path is "C:\/\/" then the result is "C:\/" because "C:"
271+ -- has a different meaning.
233272--
234273-- >>> f a = Path.toString $ Path.dropTrailingSeparators (pack a)
235274-- >>> f "./"
236275-- "."
276+ -- >>> f "//"
277+ -- "/"
237278--
238279{-# INLINE dropTrailingSeparators #-}
239280dropTrailingSeparators :: OS_PATH -> OS_PATH
240281dropTrailingSeparators (OS_PATH arr) =
241282 OS_PATH (Common. dropTrailingSeparators Common. OS_NAME arr)
242283
284+ -- | Returns True if the path has a trailing separator. This means the path is
285+ -- implicitly a dir type path.
286+ {-# INLINE hasTrailingSeparator #-}
287+ hasTrailingSeparator :: OS_PATH -> Bool
288+ hasTrailingSeparator (OS_PATH arr) =
289+ Common. hasTrailingSeparator Common. OS_NAME arr
290+
291+ -- | Add a trailing path separator if it does not have one.
292+ -- Note that this will make it an implicit dir type path.
293+ --
294+ -- Note that on Windows adding a separator to "C:" makes it "C:\\" which has a
295+ -- different meaning.
296+ --
297+ {-# INLINE addTrailingSeparator #-}
298+ addTrailingSeparator :: OS_PATH -> OS_PATH
299+ addTrailingSeparator p = unsafeAppend p sep
300+
301+ where
302+
303+ sep = fromJust $ fromString [Common. primarySeparator Common. OS_NAME ]
304+
243305-- | Throws an exception if the path is not valid. See 'isValidPath' for the
244306-- list of validations.
245307#ifndef IS_WINDOWS
@@ -350,14 +412,23 @@ unsafeFromString =
350412 fromJust . fromString
351413#endif
352414
353- -- | Convert astring to OS_PATH. See 'fromChars' for failure cases and
415+ -- | Convert a string to OS_PATH. See 'fromChars' for failure cases and
354416-- semantics.
355417--
356418-- >>> fromString = Path.fromChars . Stream.fromList
357419--
358420fromString :: (MonadThrow m , IsPath OS_PATH a ) => [Char ] -> m a
359421fromString = fromChars . Stream. fromList
360422
423+ -- | Concatenate a string to an existing path.
424+ --
425+ -- Throws an error if the resulting path is not a valid path as per
426+ -- 'isValidPath'.
427+ --
428+ -- /Unimplemented/
429+ addString :: OS_PATH -> [Char ] -> OS_PATH
430+ addString (OS_PATH _a) = undefined
431+
361432------------------------------------------------------------------------------
362433-- Statically Verified Strings
363434------------------------------------------------------------------------------
@@ -517,21 +588,19 @@ isRooted (OS_PATH arr) = Common.isRooted Common.OS_NAME arr
517588isBranch :: OS_PATH -> Bool
518589isBranch = not . isRooted
519590
520- -- XXX This can be generalized to an Array intersperse operation
521- -- XXX This can work on a polymorphic IsPath type.
522-
591+ #ifndef IS_WINDOWS
523592-- | Like 'append' but does not check if any of the path is empty or if the
524593-- second path is rooted.
525594--
526- -- >>> append a b = Path.toString $ Path.unsafeAppend (pack a) (pack b)
595+ -- >>> f a b = Path.toString $ Path.unsafeAppend (pack a) (pack b)
527596--
528- -- >>> append "x" "y"
597+ -- >>> f "x" "y"
529598-- "x/y"
530- -- >>> append "x/" "y"
599+ -- >>> f "x/" "y"
531600-- "x/y"
532- -- >>> append "x" "/y"
601+ -- >>> f "x" "/y"
533602-- "x/y"
534- -- >>> append "x/" "/y"
603+ -- >>> f "x/" "/y"
535604-- "x/y"
536605--
537606{-# INLINE unsafeAppend #-}
@@ -541,13 +610,12 @@ unsafeAppend (OS_PATH a) (OS_PATH b) =
541610 $ Common. unsafeAppend
542611 Common. OS_NAME (Common. toString Unicode. UNICODE_DECODER ) a b
543612
544- -- XXX Should we fail if the first path does not have a trailing separator i.e.
545- -- it is not a directory?
613+ -- XXX rename it to extend or combine?
546614
547- #ifndef IS_WINDOWS
548615-- | Append a OS_PATH to another. Fails if the second path refers to a rooted
549- -- path. Use 'unsafeAppend' to avoid failure if you know it is ok to append the
550- -- path or use the typesafe Streamly.FileSystem.OS_PATH.Seg module.
616+ -- path. If you want to avoid runtime failure use the typesafe
617+ -- Streamly.FileSystem.OS_PATH.Seg module. Use 'unsafeAppend' to avoid failure
618+ -- if you know it is ok to append the path.
551619--
552620-- >>> f a b = Path.toString $ Path.append a b
553621--
@@ -582,7 +650,7 @@ append'
582650#endif
583651
584652-- XXX This can be pure, like append.
585- -- XXX add appendW16CString for Windows?
653+ -- XXX add appendCWString for Windows?
586654
587655#ifndef IS_WINDOWS
588656-- | Append a separator and a CString to the Array. This is like 'unsafeAppend'
@@ -606,6 +674,17 @@ appendCString'
606674 Common. OS_NAME a str
607675#endif
608676
677+ -- See unsafeJoinPaths in the Common path module, we need to avoid MonadIo from
678+ -- that to implement this.
679+
680+ -- | Join paths by path separator. Does not check if the paths being appended
681+ -- are rooted or branches. Note that splitting and joining may not give exactly
682+ -- the original path but an equivalent path.
683+ --
684+ -- /Unimplemented/
685+ unsafeJoinPaths :: [OS_PATH ] -> OS_PATH
686+ unsafeJoinPaths = undefined
687+
609688------------------------------------------------------------------------------
610689-- Splitting path
611690------------------------------------------------------------------------------
@@ -615,6 +694,16 @@ appendCString'
615694-- otherwise root is returned as empty. If the path is rooted then the non-root
616695-- part is guaranteed to not start with a separator.
617696--
697+ -- Some filepath package equivalent idioms:
698+ --
699+ -- >>> splitDrive = Path.splitRoot
700+ -- >>> joinDrive = Path.unsafeAppend
701+ -- >>> takeDrive = fst . Path.splitRoot
702+ -- >>> dropDrive = snd . Path.splitRoot
703+ --
704+ -- >> hasDrive = not . null . takeDrive -- TODO
705+ -- >> isDrive = null . dropDrive -- TODO
706+ --
618707-- >>> toList (a,b) = (Path.toString a, Path.toString b)
619708-- >>> split = toList . Path.splitRoot . pack
620709--
@@ -760,6 +849,15 @@ splitPath_ (OS_PATH a) = fmap OS_PATH $ Common.splitPath_ Common.OS_NAME a
760849--
761850-- If the path cannot be a file then (path, "") is returned.
762851--
852+ -- Some filepath package equivalent idioms:
853+ --
854+ -- >>> takeFileName = snd . Path.splitFile -- Posix basename
855+ -- >>> takeBaseName = fst . Path.splitExtension . snd . Path.splitFile
856+ -- >>> dropFileName = fst . Path.splitFile
857+ -- >>> takeDirectory = fst . Path.splitFile
858+ -- >>> replaceFileName p x = Path.append (takeDirectory p) x
859+ -- >>> replaceDirectory p x = Path.append x (takeFileName p)
860+ --
763861-- >>> toList (a,b) = (Path.toString a, Path.toString b)
764862-- >>> split = toList . Path.splitFile . pack
765863--
@@ -803,16 +901,31 @@ splitFile (OS_PATH a) =
803901 bimap OS_PATH OS_PATH $ Common. splitFile Common. OS_NAME a
804902
805903#ifndef IS_WINDOWS
806- -- | For the purposes of this function a file is considered to have an
807- -- extension if the file name can be broken down into a non-empty filename
808- -- followed by an extension separator (usually ".") followed by a non-empty
809- -- extension with at least one character other than the extension separator
810- -- characters. The shortest suffix obtained by this rule, starting with the
811- -- extension separator is returned as the extension and the remaining prefix
904+ -- Note: In the cases of "x.y." and "x.y.." we return no extension rather
905+ -- than ".y." or ".y.." as extensions. That is they considered to have no
906+ -- extension.
907+
908+ -- | A file name is considered to have an extension if the file name can be
909+ -- split into a non-empty filename followed by the extension separator "."
910+ -- followed by a non-empty extension with at least one character in addition to
911+ -- the extension separator.
912+ -- The shortest suffix obtained by this rule, starting with the
913+ -- extension separator, is returned as the extension and the remaining prefix
812914-- part as the filename.
813915--
814916-- A directory name does not have an extension.
815917--
918+ -- Other extension related operations can be implemented using this API:
919+ --
920+ -- >>> takeExtension = snd . Path.splitExtension
921+ -- >>> dropExtension = fst . Path.splitExtension
922+ --
923+ -- >> hasExtension = not . null . takeExtension -- TODO
924+ --
925+ -- If you want a @splitExtensions@, you can splitExtension until the extension
926+ -- returned is empty. @dropExtensions@, @isExtensionOf@ can be implemented
927+ -- similarly.
928+ --
816929-- >>> toList (a,b) = (Path.toString a, Path.toString b)
817930-- >>> split = toList . Path.splitExtension . pack
818931--
@@ -846,10 +959,10 @@ splitFile (OS_PATH a) =
846959-- >>> split "/x.y"
847960-- ("/x",".y")
848961--
849- -- >>> split "/x.y." -- XXX should it be .y.?
962+ -- >>> split "/x.y."
850963-- ("/x.y.","")
851964--
852- -- >>> split "/x.y.." -- XXX should it be .y..?
965+ -- >>> split "/x.y.."
853966-- ("/x.y..","")
854967--
855968-- >>> split "x/.y"
@@ -893,6 +1006,16 @@ splitExtension (OS_PATH a) =
8931006 bimap OS_PATH OS_PATH $ Common. splitExtension Common. OS_NAME a
8941007#endif
8951008
1009+ -- | Add an extension to a file path. If a non-empty extension does not start
1010+ -- with a leading dot then a dot is inserted, otherwise the extension is
1011+ -- concatenated with the path.
1012+ --
1013+ -- It is an error to add an extension to a path with a trailing separator.
1014+ --
1015+ -- /Unimplemented/
1016+ addExtension :: OS_PATH -> OS_PATH -> OS_PATH
1017+ addExtension (OS_PATH _a) = undefined
1018+
8961019------------------------------------------------------------------------------
8971020-- Path equality
8981021------------------------------------------------------------------------------
@@ -1036,3 +1159,11 @@ eqPathWith cfg (OS_PATH a) (OS_PATH b) =
10361159--
10371160eqPathBytes :: OS_PATH -> OS_PATH -> Bool
10381161eqPathBytes (OS_PATH a) (OS_PATH b) = Common. eqPathBytes a b
1162+
1163+ -- | Convert the path to an equivalent but standard format for reliable
1164+ -- comparison. This can be implemented if required. Usually, the equality
1165+ -- operations should be enough and this may not be needed.
1166+ --
1167+ -- /Unimplemented/
1168+ normalize :: EqCfg -> OS_PATH -> OS_PATH
1169+ normalize _cfg (OS_PATH _a) = undefined
0 commit comments