1
1
{-# LANGUAGE PatternGuards #-}
2
2
{-# LANGUAGE TypeApplications #-}
3
+ {-# LANGUAGE MultiWayIf #-}
3
4
4
5
-- This template expects CPP definitions for:
5
6
-- MODULE_NAME = Posix | Windows
@@ -602,6 +603,7 @@ isDrive x = not (null x) && null (dropDrive x)
602
603
-- > Posix: splitFileName "/" == ("/","")
603
604
-- > Windows: splitFileName "c:" == ("c:","")
604
605
-- > Windows: splitFileName "\\\\?\\A:\\fred" == ("\\\\?\\A:\\","fred")
606
+ -- > Windows: splitFileName "\\\\?\\A:" == ("\\\\?\\A:","")
605
607
splitFileName :: FILEPATH -> (STRING , STRING )
606
608
splitFileName x = if null path
607
609
then (dotSlash, file)
@@ -644,20 +646,43 @@ splitFileName_ fp
644
646
-- or UNC location "\\?\UNC\foo", where path separator is a part of the drive name.
645
647
-- We can test this by trying dropDrive and falling back to splitDrive.
646
648
| isWindows
647
- , Just (s1, _s2, bs') <- uncons2 dirSlash
648
- , isPathSeparator s1
649
- -- If bs' is empty, then s2 as the last character of dirSlash must be a path separator,
650
- -- so we are in the middle of shared drive.
651
- -- Otherwise, since s1 is a path separator, we might be in the middle of UNC path.
652
- , null bs' || maybe False isIncompleteUNC (readDriveUNC dirSlash)
653
- = (fp, mempty )
649
+ = case uncons2 dirSlash of
650
+ Just (s1, s2, bs')
651
+ | isPathSeparator s1
652
+ -- If bs' is empty, then s2 as the last character of dirSlash must be a path separator,
653
+ -- so we are in the middle of shared drive.
654
+ -- Otherwise, since s1 is a path separator, we might be in the middle of UNC path.
655
+ , null bs' || maybe False isIncompleteUNC (readDriveUNC dirSlash)
656
+ -> (fp, mempty )
657
+ -- This handles inputs like "//?/A:" and "//?/A:foo"
658
+ | isPathSeparator s1
659
+ , isPathSeparator s2
660
+ , Just (s3, s4, bs'') <- uncons2 bs'
661
+ , s3 == _question
662
+ , isPathSeparator s4
663
+ , null bs''
664
+ , Just (drive, rest) <- readDriveLetter file
665
+ -> (dirSlash <> drive, rest)
666
+ _ -> (dirSlash, file)
654
667
| otherwise
655
- = (dirSlash, file)
668
+ = (dirSlash, file)
656
669
where
657
670
(dirSlash, file) = breakEnd isPathSeparator fp
658
-
671
+ dropExcessTrailingPathSeparators x
672
+ | hasTrailingPathSeparator x
673
+ , let x' = dropWhileEnd isPathSeparator x
674
+ , otherwise = if | null x' -> singleton (last x)
675
+ | otherwise -> addTrailingPathSeparator x'
676
+ | otherwise = x
677
+
678
+ -- an "incomplete" UNC is one without a path (but potentially a drive)
659
679
isIncompleteUNC (pref, suff) = null suff && not (hasPenultimateColon pref)
660
- hasPenultimateColon = maybe False (maybe False ((== _colon) . snd ) . unsnoc . fst ) . unsnoc
680
+
681
+ -- e.g. @//?/a:/@ or @//?/a://@, but not @//?/a:@
682
+ hasPenultimateColon pref
683
+ | hasTrailingPathSeparator pref
684
+ = maybe False (maybe False ((== _colon) . snd ) . unsnoc . fst ) . unsnoc . dropExcessTrailingPathSeparators $ pref
685
+ | otherwise = False
661
686
662
687
-- | Set the filename.
663
688
--
@@ -671,6 +696,7 @@ replaceFileName x y = a </> y where (a,_) = splitFileName_ x
671
696
--
672
697
-- > dropFileName "/directory/file.ext" == "/directory/"
673
698
-- > dropFileName x == fst (splitFileName x)
699
+ -- > isPrefixOf (takeDrive x) (dropFileName x)
674
700
dropFileName :: FILEPATH -> FILEPATH
675
701
dropFileName = fst . splitFileName
676
702
0 commit comments