streamly-core
Copyright(c) 2023 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.FileSystem.WindowsPath

Description

This module implements a WindowsPath type representing a file system path for Windows operating systems. The only assumption about the encoding of the path is that it maps the characters /, \ and . to Word16 representing their ASCII values. Operations are provided to encode and decode using UTF-16LE encoding.

This module has APIs that are equivalent to or can emulate all or most of the filepath package APIs. It has some differences from the filepath package:

  • Empty paths are not allowed. Paths are validated before construction.
  • The default Path type itself affords considerable safety regarding the distinction of rooted or non-rooted paths, it also allows distinguishing directory and file paths.
  • It is designed to provide flexible typing to provide compile time safety for rootednon-rooted paths and filedir paths. The Path type is just part of that typed path ecosystem. Though the default Path type itself should be enough for most cases.
  • It leverages the streamly array module for most of the heavy lifting, it is a thin wrapper on top of that, improving maintainability as well as providing better performance. We can have pinned and unpinned paths, also provide lower level operations for certain cases to interact more efficinetly with low level code.
Synopsis

Setup

To execute the code examples provided in this module in ghci, please run the following commands first.

>>> :m
>>> :set -XQuasiQuotes
>>> import Control.Exception (SomeException, evaluate, try)
>>> import Data.Either (Either, isLeft)
>>> import Data.Maybe (fromJust, isNothing, isJust)
>>> import Data.Word (Word16)
>>> import Streamly.Data.Array (Array)
>>> import qualified Streamly.Data.Array as Array
>>> import qualified Streamly.Data.Stream as Stream
>>> import qualified Streamly.Unicode.Stream as Unicode

For APIs that have not been released yet.

>>> import Streamly.Internal.FileSystem.WindowsPath (WindowsPath, path)
>>> import qualified Streamly.Internal.FileSystem.WindowsPath as Path

Utilities:

>>> fails x = isLeft <$> (try (evaluate x) :: IO (Either SomeException String))

Type

newtype WindowsPath Source #

A type representing file system paths on Windows.

A WindowsPath is validated before construction unless unsafe constructors are used to create it. For validations performed by the safe construction methods see the fromChars function.

Note that in some cases the file system may perform unicode normalization on paths (e.g. Apple HFS), it may cause surprising results as the path used by the user may not have the same bytes as later returned by the file system.

Constructors

WindowsPath (Array Word16) 

Instances

Instances details
IsPath WindowsPath WindowsPath Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath

IsPath WindowsPath (Dir WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Node

IsPath WindowsPath (File WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Node

IsPath WindowsPath (Rooted WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Seg

IsPath WindowsPath (Rooted (Dir WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Rooted (File WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Unrooted WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Seg

IsPath WindowsPath (Unrooted (Dir WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Unrooted (File WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

Conversions

class IsPath a b where Source #

If the type a b is a member of IsPath it means we know how to convert the type b to and from the base type a.

Methods

unsafeFromPath :: a -> b Source #

Like fromPath but does not check the properties of Path. The user is responsible to maintain the invariants enforced by the type b otherwise surprising behavior may result.

This operation provides performance and simplicity when we know that the properties of the path are already verified, for example, when we get the path from the file system or from the OS APIs.

fromPath :: MonadThrow m => a -> m b Source #

Convert a base path type to other forms of well-typed paths. It may fail if the path does not satisfy the properties of the target type.

toPath :: b -> a Source #

Convert a well-typed path to the base path type. Never fails.

Instances

Instances details
IsPath PosixPath PosixPath Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath

IsPath WindowsPath WindowsPath Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath

IsPath PosixPath (Dir PosixPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.Node

IsPath PosixPath (File PosixPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.Node

IsPath PosixPath (Rooted PosixPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.Seg

IsPath PosixPath (Rooted (Dir PosixPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.SegNode

IsPath PosixPath (Rooted (File PosixPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.SegNode

IsPath PosixPath (Unrooted PosixPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.Seg

IsPath PosixPath (Unrooted (Dir PosixPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.SegNode

IsPath PosixPath (Unrooted (File PosixPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.PosixPath.SegNode

IsPath WindowsPath (Dir WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Node

IsPath WindowsPath (File WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Node

IsPath WindowsPath (Rooted WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Seg

IsPath WindowsPath (Rooted (Dir WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Rooted (File WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Unrooted WindowsPath) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.Seg

IsPath WindowsPath (Unrooted (Dir WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

IsPath WindowsPath (Unrooted (File WindowsPath)) Source # 
Instance details

Defined in Streamly.Internal.FileSystem.WindowsPath.SegNode

adapt :: (MonadThrow m, IsPath WindowsPath a, IsPath WindowsPath b) => a -> m b Source #

Convert a path type to another path type. This operation may fail with a PathException when converting a less restrictive path type to a more restrictive one. This can be used to upgrade or downgrade type safety.

Conversion to OsWord

charToWord :: Char -> Word16 Source #

Unsafe, truncates the Char to Word8 on Posix and Word16 on Windows.

wordToChar :: Word16 -> Char Source #

Unsafe, should be a valid character.

Validation

validatePath :: MonadThrow m => Array Word16 -> m () Source #

Checks whether the filepath is valid; i.e., whether the operating system permits such a path for listing or creating files. These validations are operating system specific and file system independent. Throws an exception with a detailed explanation if the path is invalid.

>>> isValid = isJust . Path.validatePath . Path.encodeString

General validations:

>>> isValid ""
False
>>> isValid "\0"
False

Windows invalid characters:

>>> isValid "c::"
False
>>> isValid "c:\\x:y"
False
>>> isValid "x*"
False
>>> isValid "x\ty" -- control characters
False

Windows invalid path components:

>>> isValid "pRn.txt"
False
>>> isValid " pRn .txt"
False
>>> isValid "c:\\x\\pRn"
False
>>> isValid "c:\\x\\pRn.txt"
False
>>> isValid "c:\\pRn\\x"
False
>>> isValid "c:\\ pRn \\x"
False
>>> isValid "pRn.x.txt"
False

Windows drive root validations:

>>> isValid "c:"
True
>>> isValid "c:a\\b"
True
>>> isValid "c:\\"
True
>>> isValid "c:\\\\"
False
>>> isValid "c:\\/"
False
>>> isValid "c:\\\\x"
False
>>> isValid "c:\\/x"
False

Mixing path separators: >>> isValid "/x\y" True >>> isValid "\/" -- ? True >>> isValid "/\" -- ? True >>> isValid "\xy" -- ? True >>> isValid "x\y" -- ? True >>> isValid "x\y" -- ? True

Windows share path validations:

>>> isValid "\\"
True
>>> isValid "\\\\"
False
>>> isValid "\\\\\\"
False
>>> isValid "\\\\x"
False
>>> isValid "\\\\x\\"
True
>>> isValid "\\\\x\\y"
True
>>> isValid "//x/y"
True
>>> isValid "\\\\prn\\y"
False
>>> isValid "\\\\x\\\\"
False
>>> isValid "\\\\x\\\\x"
False
>>> isValid "\\\\\\x"
False

Windows short UNC path validations:

>>> isValid "\\\\?\\c:"
False
>>> isValid "\\\\?\\c:\\"
True
>>> isValid "\\\\?\\c:x"
False
>>> isValid "\\\\?\\c:\\\\" -- XXX validate this
False
>>> isValid "\\\\?\\c:\\x"
True
>>> isValid "\\\\?\\c:\\\\\\"
False
>>> isValid "\\\\?\\c:\\\\x"
False

Windows long UNC path validations:

>>> isValid "\\\\?\\UnC\\x" -- UnC treated as share name
True
>>> isValid "\\\\?\\UNC\\x" -- XXX fix
False
>>> isValid "\\\\?\\UNC\\c:\\x"
True

DOS local/global device namespace

>>> isValid "\\\\.\\x"
True
>>> isValid "\\\\??\\x"
True

Other than these there may be maximum path component length and maximum path length restrictions enforced by the OS as well as the filesystem which we do not validate.

isValidPath :: Array Word16 -> Bool Source #

Returns True if the filepath is valid:

>>> isValidPath = isJust . Path.validatePath

validatePath' :: MonadThrow m => Array Word16 -> m () Source #

Like validatePath but more strict. The path must refer to a file system object. For example, a share root itself is not a valid file system object. it must be followed by a non-empty path.

>>> isValid = isJust . Path.validatePath' . Path.encodeString
>>> isValid "\\\\"
False
>>> isValid "\\\\server\\"
False
>>> isValid "\\\\server\\x"
True
>>> isValid "\\\\?\\UNC\\server"
False

isValidPath' :: Array Word16 -> Bool Source #

Like isValidPath but more strict.

>>> isValidPath' = isJust . Path.validatePath'

Construction

fromArray :: MonadThrow m => Array Word16 -> m WindowsPath Source #

Convert an encoded array of Word16 into a value of type WindowsPath. The path is validated using validatePath.

Each Word16 should be encoded such that:

  • The input does not contain a NUL word.
  • The Word16 is encoded with little-endian ordering.
  • Values from 1-128 are assumed to be ASCII characters.

Apart from the above, there are no restrictions on the encoding.

To bypass path validation checks, use unsafeFromArray.

Throws InvalidPath if validatePath fails on the resulting path.

unsafeFromArray :: Array Word16 -> WindowsPath Source #

Unsafe: The user is responsible to make sure that the path is valid as per validatePath.

fromChars :: MonadThrow m => Stream Identity Char -> m WindowsPath Source #

Like fromString but a streaming operation.

>>> fromString = Path.fromChars . Stream.fromList

We do not sanitize the path i.e. we do not remove duplicate separators, redundant . segments, trailing separators etc because that would require unnecessary checks and modifications to the path which may not be used ever for any useful purpose, it is only needed for path equality and can be done during the equality check.

Unicode normalization is not done. If normalization is needed the user can normalize it and then use the fromArray API.

fromString :: MonadThrow m => [Char] -> m WindowsPath Source #

Encode a Unicode character string to WindowsPath using strict UTF-16LE encoding. The path is validated using validatePath.

fromString_ :: [Char] -> WindowsPath Source #

Like fromString but a pure and partial function that throws an InvalidPath exception.

encodeString :: [Char] -> Array Word16 Source #

Create an array from a path string using strict UTF-16LE encoding. The path is not validated, therefore, it may not be valid according to validatePath.

Same as toArray . unsafeFromString.

unsafeFromString :: [Char] -> WindowsPath Source #

Like fromString but does not perform any validations mentioned under validatePath. Fails only if unicode encoding fails.

readArray :: [Char] -> WindowsPath Source #

Read a raw array of Word16 as a path type.

>>> readArray = fromJust . Path.fromArray . read
>>> arr :: Array Word16 = Path.encodeString "hello"
>>> Path.showArray $ (Path.readArray $ show arr :: Path.WindowsPath)
"fromList [104,101,108,108,111]"

See also: showArray.

Statically Verified String Literals

Quasiquoters.

Statically Verified Strings

Template Haskell expression splices.

pathE :: String -> Q Exp Source #

Generates a Haskell expression of type WindowsPath from a String. Equivalent to using fromString on the string passed.

Elimination

toArray :: WindowsPath -> Array Word16 Source #

Convert the path to an array.

toChars :: forall (m :: Type -> Type). Monad m => WindowsPath -> Stream m Char Source #

Decode the path to a stream of Unicode chars using strict UTF-16LE decoding.

toChars_ :: forall (m :: Type -> Type). Monad m => WindowsPath -> Stream m Char Source #

Decode the path to a stream of Unicode chars using lax UTF-16LE decoding.

toString :: WindowsPath -> [Char] Source #

Decode the path to a Unicode string using strict UTF-16LE decoding.

asCWString :: WindowsPath -> (CWString -> IO a) -> IO a Source #

Use the path as a pinned CWString. Useful for using a WindowsPath in system calls on Windows.

toString_ :: WindowsPath -> [Char] Source #

Decode the path to a Unicode string using lax UTF-16LE decoding.

showArray :: WindowsPath -> [Char] Source #

Show the path as raw characters without any specific decoding.

See also: readArray.

Separators

separator :: Word16 Source #

The primary path separator word: / on POSIX and \ on Windows. Windows also supports / as a valid separator. Use isSeparator to check for any valid path separator.

isSeparator :: Word16 -> Bool Source #

On POSIX, only / is a path separator, whereas on Windows both / and \ are valid separators.

extSeparator :: Word16 Source #

File extension separator word.

Dir or non-dir paths

dropTrailingSeparators :: WindowsPath -> WindowsPath Source #

Remove all trailing path separators from the given Path.

Instead of this operation you may want to use eqPath with ignoreTrailingSeparators option.

This operation is careful not to alter the semantic meaning of the path. For example, on Windows:

  • Dropping the separator from "C:/" would change the meaning of the path from referring to the root of the C: drive to the current directory on C:.
  • If a path ends with a separator immediately after a colon (e.g., "C:/"), the separator will not be removed.

If the input path is invalid, the behavior is not fully guaranteed:

  • The separator may still be dropped.
  • In some cases, dropping the separator may make an invalid path valid (e.g., "C:\\" or "C:\/").

This operation may convert a path that implicitly refers to a directory into one that does not.

Typically, if the path is dir//, the result is dir. Special cases include:

  • On POSIX: dropping from "//" yields "/".
  • On Windows: dropping from "C://" results in "C:/".

Examples:

>>> f = Path.toString . Path.dropTrailingSeparators . Path.fromString_
>>> f "./"
"."
> f "//"  -- On POSIX

"/"

hasTrailingSeparator :: WindowsPath -> Bool Source #

Returns True if the path ends with a trailing separator.

This typically indicates that the path is a directory, though this is not guaranteed in all cases.

Example:

>>> Path.hasTrailingSeparator (Path.fromString_ "foo/")
True
>>> Path.hasTrailingSeparator (Path.fromString_ "foo")
False

addTrailingSeparator :: WindowsPath -> WindowsPath Source #

Add a trailing path separator to a path if it doesn't already have one.

Instead of this operation you may want to use eqPath with ignoreTrailingSeparators option.

This function avoids modifying the path if doing so would change its meaning or make it invalid. For example, on Windows:

  • Adding a separator to "C:" would change it from referring to the current directory on the C: drive to the root directory.
  • Adding a separator to "\" could turn it into a UNC share path, which may not be intended.
  • If the path ends with a colon (e.g., "C:"), a separator is not added.

This operation typically makes the path behave like an implicit directory path.

Path Segment Types

isRooted :: WindowsPath -> Bool Source #

A path that is attached to a root. "C:\" is considered an absolute root and "." as a dynamic root. ".." is not considered a root, "../x" or "x/y" are not rooted paths.

Absolute locations:

  • C:\ local drive
  • \\share\ UNC share
  • \\?\C:\ Long UNC local drive
  • \\?\UNC\ Long UNC remote server
  • \\.\ DOS local device namespace
  • \\??\ DOS global namespace

Relative locations:

  • \ relative to current drive root
  • .\ relative to current directory
  • C: current directory in drive
  • C:file relative to current directory in drive
>>> isRooted = Path.isRooted . fromJust . Path.fromString

Common to Windows and Posix:

>>> isRooted "/"
True
>>> isRooted "/x"
True
>>> isRooted "."
True
>>> isRooted "./x"
True

Windows specific:

>>> isRooted "c:"
True
>>> isRooted "c:x"
True
>>> isRooted "c:/"
True
>>> isRooted "//x/y"
True

isUnrooted :: WindowsPath -> Bool Source #

A path that is not attached to a root e.g. a/b/c or ../b/c.

>>> isUnrooted = not . Path.isRooted
>>> isUnrooted = Path.isUnrooted . Path.fromString_
>>> isUnrooted "x"
True
>>> isUnrooted "x/y"
True
>>> isUnrooted ".."
True
>>> isUnrooted "../x"
True

Joining

joinStr :: WindowsPath -> [Char] -> WindowsPath Source #

Append a separator followed by the supplied string to a path.

Throws InvalidPath if the resulting path is not a valid path as per validatePath.

unsafeJoin :: WindowsPath -> WindowsPath -> WindowsPath Source #

Like join but does not check if any of the path is empty or if the second path is rooted.

>>> f a b = Path.toString $ Path.unsafeJoin (Path.fromString_ a) (Path.fromString_ b)
>>> f "x" "y"
"x\\y"
>>> f "x/" "y"
"x/y"
>>> f "x" "/y"
"x/y"
>>> f "x/" "/y"
"x/y"

Note "c:" and "/x" are both rooted paths, therefore, join cannot be used to join them. Similarly for joining "/x" and "/y". For these cases use unsafeJoin. unsafeJoin can be used as a replacement for the joinDrive function from the filepath package.

>>> f "c:" "/x"
"c:/x"
>>> f "//x/" "/y"
"//x/y"

join :: WindowsPath -> WindowsPath -> WindowsPath Source #

Append a WindowsPath to another. Fails if the second path refers to a rooted path. If you want to avoid runtime failure use the typesafe Streamly.FileSystem.WindowsPath.Seg module. Use unsafeJoin to avoid failure if you know it is ok to append the path.

Usually, append joins two paths using a separator between the paths. On Windows, joining a drive "c:" with path "x" does not add a separator between the two because "c:x" is different from "c:/x".

Note "c:" and "/x" are both rooted paths, therefore, join cannot be used to join them. Similarly for joining "/x" and "/y". For these cases use unsafeJoin.

>>> f a b = Path.toString $ Path.join a b
>>> f [path|x|] [path|y|]
"x\\y"
>>> f [path|x/|] [path|y|]
"x/y"
>>> f [path|c:|] [path|x|]
"c:x"
>>> f [path|c:/|] [path|x|]
"c:/x"
>>> f [path|//x/|] [path|y|]
"//x/y"
>>> fails $ f [path|c:|] [path|/|]
True
>>> fails $ f [path|c:|] [path|/x|]
True
>>> fails $ f [path|c:/|] [path|/x|]
True
>>> fails $ f [path|//x/|] [path|/y|]
True

joinDir :: WindowsPath -> WindowsPath -> WindowsPath Source #

A stricter version of join which requires the first path to be a directory like path i.e. with a trailing separator.

>>> f a b = Path.toString $ Path.joinDir a b
>>> fails $ f [path|x|] [path|y|]
True

unsafeJoinPaths :: [WindowsPath] -> WindowsPath Source #

Join paths by path separator. Does not check if the paths being appended are rooted or branches. Note that splitting and joining may not give exactly the original path but an equivalent path.

Unimplemented

Splitting

Note: you can use unsafeJoin as a replacement for the joinDrive function in the filepath package.

splitRoot :: WindowsPath -> Maybe (WindowsPath, Maybe WindowsPath) Source #

If a path is rooted then separate the root and the remaining path, otherwise root is returned as empty. If the path is rooted then the non-root part is guaranteed to not start with a separator.

See Streamly.Internal.FileSystem.PosixPath module for common examples. We provide some Windows specific examples here.

>>> toList (a,b) = (Path.toString a, fmap Path.toString b)
>>> split = fmap toList . Path.splitRoot . Path.fromString_
>>> split "c:"
Just ("c:",Nothing)
>>> split "c:/"
Just ("c:/",Nothing)
>>> split "//x/"
Just ("//x/",Nothing)
>>> split "//x/y"
Just ("//x/",Just "y")

splitPath :: forall (m :: Type -> Type). Monad m => WindowsPath -> Stream m WindowsPath Source #

Split the path components keeping separators between path components attached to the dir part. Redundant separators are removed, only the first one is kept, but separators are not changed to the default on Windows. Separators are not added either e.g. "." and ".." may not have trailing separators if the original path does not.

>>> split = Stream.toList . fmap Path.toString . Path.splitPath . Path.fromString_
>>> split "/x"
["/","x"]
>>> split "/x/\\y"
["/","x/","y"]
>>> split "\\x/\\y" -- this is not valid, multiple seps after share?
["\\","x/","y"]

splitPath_ :: forall (m :: Type -> Type). Monad m => WindowsPath -> Stream m WindowsPath Source #

Split a path into components separated by the path separator. "." components in the path are ignored except when in the leading position. Trailing separators in non-root components are dropped.

>>> split = Stream.toList . fmap Path.toString . Path.splitPath_ . Path.fromString_
>>> split "c:x"
["c:","x"]
>>> split "c:/" -- Note, c:/ is not the same as c:
["c:/"]
>>> split "c:/x"
["c:/","x"]
>>> split "//x/y/"
["//x","y"]
>>> split "./a"
[".","a"]
>>> split "c:./a"
["c:","a"]
>>> split "a/."
["a"]
>>> split "/x"
["/","x"]
>>> split "/x/\\y"
["/","x","y"]
>>> split "\\x/\\y"
["\\","x","y"]

splitFile :: WindowsPath -> Maybe (Maybe WindowsPath, WindowsPath) Source #

If the path does not look like a directory then return Just (Maybe dir, file) otherwise return Nothing. The path is not a directory if:

  • the path does not end with a separator
  • the path does not end with a . or .. component

Splits a single component path into Just (Nothing, path) if it does not look like a dir.

>>> toList (a,b) = (fmap Path.toString a, Path.toString b)
>>> split = fmap toList . Path.splitFile . Path.fromString_
>>> split "/"
Nothing
>>> split "."
Nothing
>>> split "/."
Nothing
>>> split ".."
Nothing
> split "//" -- Posix

Nothing

>>> split "/home"
Just (Just "/","home")
>>> split "./home"
Just (Just "./","home")
>>> split "home"
Just (Nothing,"home")
>>> split "x/"
Nothing
>>> split "x/y"
Just (Just "x/","y")
>>> split "x//y"
Just (Just "x//","y")
>>> split "x/./y"
Just (Just "x/./","y")

splitFirst :: WindowsPath -> (WindowsPath, Maybe WindowsPath) Source #

Split the path into the first component and rest of the path. Treats the entire root or share name, if present, as the first component.

Unimplemented

splitLast :: WindowsPath -> (Maybe WindowsPath, WindowsPath) Source #

Split the path into the last component and rest of the path. Treats the entire root or share name, if present, as the first component.

>>> basename = snd . Path.splitLast -- Posix basename
>>> dirname = fst . Path.splitLast -- Posix dirname

Unimplemented

Extension

splitExtension :: WindowsPath -> Maybe (WindowsPath, WindowsPath) Source #

See Streamly.Internal.FileSystem.PosixPath module for detailed documentation and examples. We provide some Windows specific examples here.

Note: On Windows we cannot create a file named "prn." or "prn..". Thus it considers anything starting with and including the first "." as the extension and the part before it as the filename. Our definition considers "prn." as a filename without an extension.

>>> toList (a,b) = (Path.toString a, Path.toString b)
>>> split = fmap toList . Path.splitExtension . Path.fromString_
>>> split "x:y"
Nothing
>>> split "x:.y"
Nothing

dropExtension :: WindowsPath -> WindowsPath Source #

Drop the extension of a file if it has one.

>>> dropExtension p = maybe p fst $ Path.splitExtension p
>>> Path.toString $ Path.dropExtension [path|/home/user/file.txt|]
"/home/user/file"

addExtension :: WindowsPath -> WindowsPath -> WindowsPath Source #

Add an extension to a file path. If a non-empty extension does not start with a leading dot then a dot is inserted, otherwise the extension is concatenated with the path.

It is an error to add an extension to a path with a trailing separator.

Unimplemented

Path View

takeFileName :: WindowsPath -> Maybe WindowsPath Source #

Extracts the file name component (with extension) from a WindowsPath, if present.

>>> takeFileName = fmap snd . Path.splitFile
>>> replaceDirectory p x = fmap (flip Path.join x) (takeFileName p)
>>> fmap Path.toString $ Path.takeFileName [path|/home/user/file.txt|]
Just "file.txt"
>>> fmap Path.toString $ Path.takeFileName [path|/home/user/|]
Nothing

See splitFile for more examples.

takeDirectory :: WindowsPath -> Maybe WindowsPath Source #

Returns the parent directory of the given WindowsPath, if any.

>>> takeDirectory x = Path.splitFile x >>= fst
>>> replaceFileName p x = fmap (flip Path.join x) (takeDirectory p)

To get an equivalent to takeDirectory from filepath use dropTrailingSeparators on the result.

>>> fmap Path.toString $ Path.takeDirectory [path|/home/user/file.txt|]
Just "/home/user/"
>>> fmap Path.toString $ Path.takeDirectory [path|file.txt|]
Nothing

takeExtension :: WindowsPath -> Maybe WindowsPath Source #

Take the extension of a file if it has one.

>>> takeExtension = fmap snd . Path.splitExtension
>>> hasExtension = isJust . Path.splitExtension
>>> fmap Path.toString $ Path.takeExtension [path|/home/user/file.txt|]
Just ".txt"

See splitExtension for more examples.

takeFileBase :: WindowsPath -> Maybe WindowsPath Source #

Extracts the file name dropping the extension, if any, from a WindowsPath.

>>> takeFileBase = fmap Path.dropExtension . Path.takeFileName
>>> fmap Path.toString $ Path.takeFileBase [path|/home/user/file.txt|]
Just "file"
>>> fmap Path.toString $ Path.takeFileBase [path|/home/user/file|]
Just "file"
>>> fmap Path.toString $ Path.takeFileBase [path|/home/user/.txt|]
Just ".txt"
>>> fmap Path.toString $ Path.takeFileBase [path|/home/user/|]
Nothing

See splitFile for more examples.

Equality

data EqCfg Source #

Options for path comparison operation. By default path comparison uses a strict criteria for equality. The following options are provided to control the strictness.

The default configuration is as follows:

>>> :{
defaultMod = ignoreTrailingSeparators False
           . ignoreCase False
           . allowRelativeEquality False
:}

ignoreTrailingSeparators :: Bool -> EqCfg -> EqCfg Source #

When set to False (default):

>>> cfg = Path.ignoreTrailingSeparators False
>>> eq a b = Path.eqPath cfg (Path.fromString_ a) (Path.fromString_ b)
>>> eq "x/"  "x"
False

When set to True:

>>> cfg = Path.ignoreTrailingSeparators True
>>> eq a b = Path.eqPath cfg (Path.fromString_ a) (Path.fromString_ b)
>>> eq "x/"  "x"
True

Default: False

ignoreCase :: Bool -> EqCfg -> EqCfg Source #

When set to False, comparison is case sensitive.

Posix Default: False

Windows Default: True

allowRelativeEquality :: Bool -> EqCfg -> EqCfg Source #

Allow relative paths to be treated as equal. When this is False relative paths will never match even if they are literally equal e.g. "./x" will not match "./x" because the meaning of "." in both cases could be different depending on what the user meant by current directory in each case.

When set to False (default):

>>> cfg = Path.allowRelativeEquality False
>>> eq a b = Path.eqPath cfg (Path.fromString_ a) (Path.fromString_ b)
>>> eq "."  "."
False
>>> eq "./x"  "./x"
False
>>> eq "./x"  "x"
False

When set to False (default):

>>> cfg = Path.allowRelativeEquality True
>>> eq a b = Path.eqPath cfg (Path.fromString_ a) (Path.fromString_ b)
>>> eq "."  "."
True
>>> eq "./x"  "./x"
True
>>> eq "./x"  "x"
True
>>> eq "./x"  "././x"
True

Default: False

eqPath :: (EqCfg -> EqCfg) -> WindowsPath -> WindowsPath -> Bool Source #

See the eqPath documentation in the Streamly.Internal.FileSystem.PosixPath module for details.

On Windows, the following is different:

  • paths are normalized by replacing forward slash path separators by backslashes.
  • default configuration uses case-insensitive comparison.
>>> :{
 eq a b = Path.eqPath id (Path.fromString_ a) (Path.fromString_ b)
:}

The cases that are different from Posix:

>>> eq "x\\y" "x/y"
True
>>> eq "x"  "X"
True
>>> eq "c:"  "C:"
False
>>> eq "c:"  "c:"
False
>>> eq "c:x"  "c:x"
False
>>> :{
 cfg = Path.ignoreTrailingSeparators True
     . Path.ignoreCase True
     . Path.allowRelativeEquality True
 eq a b = Path.eqPath cfg (Path.fromString_ a) (Path.fromString_ b)
:}
>>> eq "./x"  "x"
True
>>> eq "X/"  "x"
True
>>> eq "C:x"  "c:X"
True
>>> eq ".\\x"  "./X"
True
>>> eq "x//y"  "x/y"
True
>>> eq "x/./y"  "x/y"
True
>>> eq "x"  "x"
True

eqPathBytes :: WindowsPath -> WindowsPath -> Bool Source #

Check two paths for byte level equality. This is the most strict path equality check.

>>> eqPath a b = Path.eqPathBytes (Path.fromString_ a) (Path.fromString_ b)
>>> eqPath "x//y"  "x//y"
True
>>> eqPath "x//y"  "x/y"
False
>>> eqPath "x/./y"  "x/y"
False
>>> eqPath "x\\y" "x/y"
False
>>> eqPath "./file"  "file"
False
>>> eqPath "file/"  "file"
False

normalize :: EqCfg -> WindowsPath -> WindowsPath Source #

Convert the path to an equivalent but standard format for reliable comparison. This can be implemented if required. Usually, the equality operations should be enough and this may not be needed.

Unimplemented