11{-# LANGUAGE PatternGuards #-}
22{-# LANGUAGE TypeApplications #-}
3+ {-# LANGUAGE MultiWayIf #-}
34
45-- This template expects CPP definitions for:
56-- MODULE_NAME = Posix | Windows
@@ -602,6 +603,7 @@ isDrive x = not (null x) && null (dropDrive x)
602603-- > Posix: splitFileName "/" == ("/","")
603604-- > Windows: splitFileName "c:" == ("c:","")
604605-- > Windows: splitFileName "\\\\?\\A:\\fred" == ("\\\\?\\A:\\","fred")
606+ -- > Windows: splitFileName "\\\\?\\A:" == ("\\\\?\\A:","")
605607splitFileName :: FILEPATH -> (STRING , STRING )
606608splitFileName x = if null path
607609 then (dotSlash, file)
@@ -644,20 +646,43 @@ splitFileName_ fp
644646 -- or UNC location "\\?\UNC\foo", where path separator is a part of the drive name.
645647 -- We can test this by trying dropDrive and falling back to splitDrive.
646648 | 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)
654667 | otherwise
655- = (dirSlash, file)
668+ = (dirSlash, file)
656669 where
657670 (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)
659679 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
661686
662687-- | Set the filename.
663688--
@@ -671,6 +696,7 @@ replaceFileName x y = a </> y where (a,_) = splitFileName_ x
671696--
672697-- > dropFileName "/directory/file.ext" == "/directory/"
673698-- > dropFileName x == fst (splitFileName x)
699+ -- > isPrefixOf (takeDrive x) (dropFileName x)
674700dropFileName :: FILEPATH -> FILEPATH
675701dropFileName = fst . splitFileName
676702
0 commit comments