11{-# LANGUAGE TemplateHaskell #-}
22
3+ #if defined(IS_PORTABLE)
4+ #define OS_PATH_TYPE Path
5+ #define OS_WORD_TYPE OsWord
6+ #define OS_CSTRING_TYPE OsCString
7+ #define AS_OS_CSTRING asOsCString
8+ #elif defined(IS_WINDOWS)
9+ #define OS_PATH_TYPE WindowsPath
10+ #define OS_WORD_TYPE Word16
11+ #define OS_CSTRING_TYPE CWString
12+ #define AS_OS_CSTRING asCWString
13+ #else
14+ #define OS_PATH_TYPE PosixPath
15+ #define OS_WORD_TYPE Word8
16+ #define OS_CSTRING_TYPE CString
17+ #define AS_OS_CSTRING asCString
18+ #endif
19+
320-- Anything other than windows (Linux/macOS/FreeBSD) is Posix
421#if defined(IS_WINDOWS)
522#define OS_NAME Windows
623#define OS_PATH WindowsPath
7- #define OS_PATH_TYPE WindowsPath
8- #define FS_WORD Word16
9- #define REAL_FS_WORD Word16
10- #define FS_CSTRING CWString
11- #define REAL_FS_CSTRING CWString
12- #define AS_FS_CSTRING asCWString
24+ #define OS_WORD Word16
25+ #define OS_CSTRING CWString
1326#define UNICODE_ENCODER encodeUtf16le'
1427#define UNICODE_DECODER decodeUtf16le'
1528#define UNICODE_DECODER_LAX decodeUtf16le
1831#else
1932#define OS_NAME Posix
2033#define OS_PATH PosixPath
21- #define OS_PATH_TYPE PosixPath
22- #define FS_WORD Word8
23- #define REAL_FS_WORD Word8
24- #define FS_CSTRING CString
25- #define REAL_FS_CSTRING CString
26- #define AS_FS_CSTRING asCString
34+ #define OS_WORD Word8
35+ #define OS_CSTRING CString
2736#define UNICODE_ENCODER encodeUtf8'
2837#define UNICODE_DECODER decodeUtf8'
2938#define UNICODE_DECODER_LAX decodeUtf8
3039#define CODEC_NAME UTF-8
3140#define SEPARATORS @/@
3241#endif
3342
34- #if defined(IS_PORTABLE)
35- #undef OS_PATH_TYPE
36- #define OS_PATH_TYPE Path
37- #undef FS_WORD
38- #define FS_WORD FsWord
39- #undef FS_CSTRING
40- #define FS_CSTRING FsCString
41- #undef AS_FS_CSTRING
42- #define AS_FS_CSTRING asFsCString
43- #endif
44-
4543-- |
4644-- Module : Streamly.Internal.FileSystem.OS_PATH_TYPE
4745-- Copyright : (c) 2023 Composewell Technologies
5149--
5250-- This module implements a OS_PATH_TYPE type representing a file system path for
5351-- OS_NAME operating systems. The only assumption about the encoding of the
54- -- path is that it maps the characters SEPARATORS and @.@ to FS_WORD
52+ -- path is that it maps the characters SEPARATORS and @.@ to OS_WORD_TYPE
5553-- representing their ASCII values. Operations are provided to encode and
5654-- decode using CODEC_NAME encoding.
5755--
@@ -76,8 +74,8 @@ module Streamly.Internal.FileSystem.OS_PATH_TYPE
7674 (
7775 -- * Type
7876#if defined(IS_PORTABLE)
79- FS_WORD
80- , FS_CSTRING
77+ OS_WORD_TYPE
78+ , OS_CSTRING_TYPE
8179 , OS_PATH_TYPE
8280#else
8381 OS_PATH_TYPE (.. )
@@ -123,7 +121,7 @@ module Streamly.Internal.FileSystem.OS_PATH_TYPE
123121 , toChars
124122 , toChars_
125123 , toString
126- , AS_FS_CSTRING
124+ , AS_OS_CSTRING
127125 , toString_
128126 , showRaw
129127
@@ -260,7 +258,11 @@ For APIs that have not been released yet.
260258-- Path components may have limits.
261259-- Total path length may have a limit.
262260
263- #if !defined(IS_PORTABLE)
261+ #if defined(IS_PORTABLE)
262+ type OS_PATH_TYPE = OS_PATH
263+ type OS_WORD_TYPE = OS_WORD
264+ type OS_CSTRING_TYPE = OS_CSTRING
265+ #else
264266-- | A type representing file system paths on OS_NAME.
265267--
266268-- A OS_PATH_TYPE is validated before construction unless unsafe constructors are
@@ -270,7 +272,7 @@ For APIs that have not been released yet.
270272-- Note that in some cases the file system may perform unicode normalization on
271273-- paths (e.g. Apple HFS), it may cause surprising results as the path used by
272274-- the user may not have the same bytes as later returned by the file system.
273- newtype OS_PATH = OS_PATH (Array FS_WORD )
275+ newtype OS_PATH = OS_PATH (Array OS_WORD_TYPE )
274276
275277-- XXX The Eq instance may be provided but it will require some sensible
276278-- defaults for comparison. For example, should we use case sensitive or
@@ -281,10 +283,6 @@ instance IsPath OS_PATH OS_PATH where
281283 unsafeFromPath = id
282284 fromPath = pure
283285 toPath = id
284- #else
285- type OS_PATH_TYPE = OS_PATH
286- type FS_WORD = REAL_FS_WORD
287- type FS_CSTRING = REAL_FS_CSTRING
288286#endif
289287
290288-- XXX Use rewrite rules to eliminate intermediate conversions for better
@@ -348,7 +346,7 @@ addTrailingSeparator p = unsafeExtend p sep
348346
349347-- | Throws an exception if the path is not valid. See 'isValidPath' for the
350348-- list of validations.
351- validatePath :: MonadThrow m => Array FS_WORD -> m ()
349+ validatePath :: MonadThrow m => Array OS_WORD_TYPE -> m ()
352350validatePath = Common. validatePath Common. OS_NAME
353351
354352#ifndef IS_WINDOWS
@@ -362,7 +360,7 @@ validatePath = Common.validatePath Common.OS_NAME
362360-- >>> isValid "\0"
363361-- False
364362--
365- isValidPath :: Array FS_WORD -> Bool
363+ isValidPath :: Array OS_WORD_TYPE -> Bool
366364isValidPath = Common. isValidPath Common. OS_NAME
367365#endif
368366
@@ -382,7 +380,7 @@ isValidPath = Common.isValidPath Common.OS_NAME
382380-- per 'isValidPath'.
383381--
384382{-# INLINE unsafeFromChunk #-}
385- unsafeFromChunk :: IsPath OS_PATH_TYPE a => Array FS_WORD -> a
383+ unsafeFromChunk :: IsPath OS_PATH_TYPE a => Array OS_WORD_TYPE -> a
386384unsafeFromChunk =
387385#ifndef DEBUG
388386 unsafeFromPath . OS_PATH . Common. unsafeFromChunk
@@ -395,7 +393,7 @@ unsafeFromChunk =
395393-- | Convert a byte array into a Path.
396394-- Throws 'InvalidPath' if 'isValidPath' fails on the path.
397395--
398- fromChunk :: (MonadThrow m , IsPath OS_PATH_TYPE a ) => Array FS_WORD -> m a
396+ fromChunk :: (MonadThrow m , IsPath OS_PATH_TYPE a ) => Array OS_WORD_TYPE -> m a
399397fromChunk arr = Common. fromChunk Common. OS_NAME arr >>= fromPath . OS_PATH
400398
401399-- XXX Should be a Fold instead?
@@ -423,7 +421,7 @@ fromChars s =
423421
424422-- | Create a raw path i.e. an array representing the path. Note that the path
425423-- is not validated, therefore, it may not be valid according to 'isValidPath'.
426- rawFromString :: [Char ] -> Array FS_WORD
424+ rawFromString :: [Char ] -> Array OS_WORD_TYPE
427425rawFromString =
428426 Common. unsafeFromChars Unicode. UNICODE_ENCODER
429427 . Stream. fromList
@@ -504,7 +502,7 @@ path = mkQ pathE
504502-- XXX unPath?
505503
506504-- | Convert the path to an array.
507- toChunk :: IsPath OS_PATH_TYPE a => a -> Array FS_WORD
505+ toChunk :: IsPath OS_PATH_TYPE a => a -> Array OS_WORD_TYPE
508506toChunk p = let OS_PATH arr = toPath p in arr
509507
510508-- | Decode the path to a stream of Unicode chars using strict CODEC_NAME decoding.
@@ -566,15 +564,15 @@ instance Show OS_PATH where
566564#ifndef IS_WINDOWS
567565-- | Use the path as a pinned CString. Useful for using a PosixPath in
568566-- system calls on Posix.
569- {-# INLINE AS_FS_CSTRING #-}
570- AS_FS_CSTRING :: OS_PATH_TYPE -> (FS_CSTRING -> IO a ) -> IO a
571- AS_FS_CSTRING p = Array. asCStringUnsafe (toChunk p)
567+ {-# INLINE AS_OS_CSTRING #-}
568+ AS_OS_CSTRING :: OS_PATH_TYPE -> (OS_CSTRING_TYPE -> IO a ) -> IO a
569+ AS_OS_CSTRING p = Array. asCStringUnsafe (toChunk p)
572570#else
573571-- | Use the path as a pinned CWString. Useful for using a WindowsPath in
574572-- system calls on Windows.
575- {-# INLINE AS_FS_CSTRING #-}
576- AS_FS_CSTRING :: OS_PATH_TYPE -> (FS_CSTRING -> IO a ) -> IO a
577- AS_FS_CSTRING p = Array. asCWString (toChunk p)
573+ {-# INLINE AS_OS_CSTRING #-}
574+ AS_OS_CSTRING :: OS_PATH_TYPE -> (OS_CSTRING_TYPE -> IO a ) -> IO a
575+ AS_OS_CSTRING p = Array. asCWString (toChunk p)
578576#endif
579577
580578------------------------------------------------------------------------------
0 commit comments