@@ -12,7 +12,6 @@ import System.OsPath.Windows ( WindowsPath )
1212import qualified System.OsPath.Windows as WS
1313import Foreign.C.Types
1414
15- import qualified System.OsString.Windows as WS hiding (decodeFS )
1615import System.OsString.Windows ( encodeUtf , WindowsString )
1716import qualified System.Win32 as Win32
1817import qualified System.Win32.WindowsString.File as WS
@@ -43,18 +42,29 @@ import Text.Printf (printf)
4342
4443#if MIN_VERSION_filepath(1, 5, 0)
4544import System.OsString.Encoding
46- import "os-string" System.OsString.Internal.Types (WindowsString (.. ), WindowsChar (.. ))
47- import qualified "os-string" System.OsString.Data.ByteString.Short as BC
4845#else
4946import Data.Coerce (coerce )
5047import System.OsPath.Encoding
5148import "filepath" System.OsString.Internal.Types (WindowsString (.. ), WindowsChar (.. ))
5249import qualified "filepath" System.OsPath.Data.ByteString.Short.Word16 as BC
5350#endif
5451
52+ import System.IO.Error (modifyIOError , ioeSetFileName )
53+ import GHC.IO.Encoding.UTF16 (mkUTF16le )
54+ import GHC.IO.Encoding.Failure (CodingFailureMode (TransliterateCodingFailure ))
55+ import Control.Exception (displayException , Exception )
56+
57+ #if defined(LONG_PATHS)
58+ import System.IO.Error (ioeSetLocation , ioeGetLocation , catchIOError )
59+ import Data.Char (isAlpha , isAscii , toUpper )
60+ import qualified System.Win32.WindowsString.Info as WS
61+ #endif
62+
5563-- | Open a file and return the 'Handle'.
5664openFile :: WindowsPath -> IOMode -> IO Handle
57- openFile fp iomode = bracketOnError
65+ openFile fp' iomode = (`ioeSetWsPath` fp') `modifyIOError` do
66+ fp <- furnishPath fp'
67+ bracketOnError
5868 (WS. createFile
5969 fp
6070 accessMode
@@ -104,7 +114,9 @@ writeShareMode =
104114
105115-- | Open an existing file and return the 'Handle'.
106116openExistingFile :: WindowsPath -> IOMode -> IO Handle
107- openExistingFile fp iomode = bracketOnError
117+ openExistingFile fp' iomode = (`ioeSetWsPath` fp') `modifyIOError` do
118+ fp <- furnishPath fp'
119+ bracketOnError
108120 (WS. createFile
109121 fp
110122 accessMode
@@ -220,8 +232,8 @@ rand_string = do
220232 return $ WS. pack $ fmap (WS. unsafeFromChar) (printf " %x-%x-%x" r1 r2 r3)
221233
222234lenientDecode :: WindowsString -> String
223- lenientDecode ws = let utf16le' = WS. decodeWith utf16le_b ws
224- ucs2' = WS. decodeWith ucs2le ws
235+ lenientDecode wstr = let utf16le' = WS. decodeWith utf16le_b wstr
236+ ucs2' = WS. decodeWith ucs2le wstr
225237 in case (utf16le', ucs2') of
226238 (Right s, ~ _) -> s
227239 (_, Right s) -> s
@@ -248,3 +260,158 @@ any_ = coerce BC.any
248260
249261#endif
250262
263+ ioeSetWsPath :: IOError -> WindowsPath -> IOError
264+ ioeSetWsPath err =
265+ ioeSetFileName err .
266+ rightOrError .
267+ WS. decodeWith (mkUTF16le TransliterateCodingFailure )
268+
269+ rightOrError :: Exception e => Either e a -> a
270+ rightOrError (Left e) = error (displayException e)
271+ rightOrError (Right a) = a
272+
273+ -- inlined stuff from directory package
274+ furnishPath :: WindowsPath -> IO WindowsPath
275+ #if !defined(LONG_PATHS)
276+ furnishPath path = pure path
277+ #else
278+ furnishPath path = pure path
279+
280+ furnishPath' :: WindowsPath -> IO WindowsPath
281+ furnishPath' path =
282+ (toExtendedLengthPath <$> rawPrependCurrentDirectory path)
283+ `catchIOError` \ _ ->
284+ pure path
285+
286+ toExtendedLengthPath :: WindowsPath -> WindowsPath
287+ toExtendedLengthPath path =
288+ if WS. isRelative path
289+ then simplifiedPath
290+ else
291+ case WS. toChar <$> simplifiedPath' of
292+ ' \\ ' : ' ?' : ' ?' : ' \\ ' : _ -> simplifiedPath
293+ ' \\ ' : ' \\ ' : ' ?' : ' \\ ' : _ -> simplifiedPath
294+ ' \\ ' : ' \\ ' : ' .' : ' \\ ' : _ -> simplifiedPath
295+ ' \\ ' : ' \\ ' : _ ->
296+ ws " \\\\ ?\\ UNC" <> WS. pack (drop 1 simplifiedPath')
297+ _ -> ws " \\\\ ?\\ " <> simplifiedPath
298+ where simplifiedPath = simplifyWindows path
299+ simplifiedPath' = WS. unpack simplifiedPath
300+
301+ rawPrependCurrentDirectory :: WindowsPath -> IO WindowsPath
302+ rawPrependCurrentDirectory path
303+ | WS. isRelative path =
304+ ((`ioeAddLocation` " prependCurrentDirectory" ) .
305+ (`ioeSetWsPath` path)) `modifyIOError` do
306+ getFullPathName path
307+ | otherwise = pure path
308+
309+ simplifyWindows :: WindowsPath -> WindowsPath
310+ simplifyWindows path
311+ | path == mempty = mempty
312+ | drive' == ws " \\\\ ?\\ " = drive' <> subpath
313+ | otherwise = simplifiedPath
314+ where
315+ simplifiedPath = WS. joinDrive drive' subpath'
316+ (drive, subpath) = WS. splitDrive path
317+ drive' = upperDrive (normaliseTrailingSep (normalisePathSeps drive))
318+ subpath' = appendSep . avoidEmpty . prependSep . WS. joinPath .
319+ stripPardirs . expandDots . skipSeps .
320+ WS. splitDirectories $ subpath
321+
322+ upperDrive d = case WS. unpack d of
323+ c : k : s
324+ | isAlpha (WS. toChar c), WS. toChar k == ' :' , all WS. isPathSeparator s ->
325+ -- unsafeFromChar is safe here since all characters are ASCII.
326+ WS. pack (WS. unsafeFromChar (toUpper (WS. toChar c)) : WS. unsafeFromChar ' :' : s)
327+ _ -> d
328+ skipSeps =
329+ (WS. pack <$> ) .
330+ filter (not . (`elem` (pure <$> WS. pathSeparators))) .
331+ (WS. unpack <$> )
332+ stripPardirs | pathIsAbsolute || subpathIsAbsolute = dropWhile (== ws " .." )
333+ | otherwise = id
334+ prependSep | subpathIsAbsolute = (WS. pack [WS. pathSeparator] <> )
335+ | otherwise = id
336+ avoidEmpty | not pathIsAbsolute
337+ , drive == mempty || hasTrailingPathSep -- prefer "C:" over "C:."
338+ = emptyToCurDir
339+ | otherwise = id
340+ appendSep p | hasTrailingPathSep, not (pathIsAbsolute && p == mempty )
341+ = WS. addTrailingPathSeparator p
342+ | otherwise = p
343+ pathIsAbsolute = not (WS. isRelative path)
344+ subpathIsAbsolute = any WS. isPathSeparator (take 1 (WS. unpack subpath))
345+ hasTrailingPathSep = WS. hasTrailingPathSeparator subpath
346+
347+ expandDots :: [WindowsPath ] -> [WindowsPath ]
348+ expandDots = reverse . go []
349+ where
350+ go ys' xs' =
351+ case xs' of
352+ [] -> ys'
353+ x : xs
354+ | x == ws " ." -> go ys' xs
355+ | x == ws " .." ->
356+ case ys' of
357+ [] -> go (x : ys') xs
358+ y : ys
359+ | y == ws " .." -> go (x : ys') xs
360+ | otherwise -> go ys xs
361+ | otherwise -> go (x : ys') xs
362+
363+ -- | Remove redundant trailing slashes and pick the right kind of slash.
364+ normaliseTrailingSep :: WindowsPath -> WindowsPath
365+ normaliseTrailingSep path = do
366+ let path' = reverse (WS. unpack path)
367+ let (sep, path'') = span WS. isPathSeparator path'
368+ let addSep = if null sep then id else (WS. pathSeparator : )
369+ WS. pack (reverse (addSep path''))
370+
371+ normalisePathSeps :: WindowsPath -> WindowsPath
372+ normalisePathSeps p = WS. pack (normaliseChar <$> WS. unpack p)
373+ where normaliseChar c = if WS. isPathSeparator c then WS. pathSeparator else c
374+
375+ emptyToCurDir :: WindowsPath -> WindowsPath
376+ emptyToCurDir path
377+ | path == mempty = ws " ."
378+ | otherwise = path
379+
380+ ws :: String -> WindowsString
381+ ws = rightOrError . WS. encodeUtf
382+
383+ getFullPathName :: WindowsPath -> IO WindowsPath
384+ getFullPathName path =
385+ fromExtendedLengthPath <$> WS. getFullPathName (toExtendedLengthPath path)
386+
387+ ioeAddLocation :: IOError -> String -> IOError
388+ ioeAddLocation e loc = do
389+ ioeSetLocation e newLoc
390+ where
391+ newLoc = loc <> if null oldLoc then " " else " :" <> oldLoc
392+ oldLoc = ioeGetLocation e
393+
394+ fromExtendedLengthPath :: WindowsPath -> WindowsPath
395+ fromExtendedLengthPath ePath =
396+ case WS. unpack ePath of
397+ c1 : c2 : c3 : c4 : path
398+ | (WS. toChar <$> [c1, c2, c3, c4]) == " \\\\ ?\\ " ->
399+ case path of
400+ c5 : c6 : c7 : subpath@ (c8 : _)
401+ | (WS. toChar <$> [c5, c6, c7, c8]) == " UNC\\ " ->
402+ WS. pack (c8 : subpath)
403+ drive : col : subpath
404+ -- if the path is not "regular", then the prefix is necessary
405+ -- to ensure the path is interpreted literally
406+ | WS. toChar col == ' :' , isDriveChar drive, isPathRegular subpath ->
407+ WS. pack path
408+ _ -> ePath
409+ _ -> ePath
410+ where
411+ isDriveChar drive = isAlpha (WS. toChar drive) && isAscii (WS. toChar drive)
412+ isPathRegular path =
413+ not (' /' `elem` (WS. toChar <$> path) ||
414+ ws " ." `elem` WS. splitDirectories (WS. pack path) ||
415+ ws " .." `elem` WS. splitDirectories (WS. pack path))
416+
417+ #endif
0 commit comments