Skip to content
Snippets Groups Projects
Commit 486373cb authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Minor refactorings as suggested by hlint

parent 78748dc2
No related branches found
No related merge requests found
...@@ -87,7 +87,7 @@ module System.FilePath.MODULE_NAME ...@@ -87,7 +87,7 @@ module System.FilePath.MODULE_NAME
) )
where where
import Data.Char(toLower, toUpper) import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper)
import Data.Maybe(isJust, fromJust) import Data.Maybe(isJust, fromJust)
import Data.List(isPrefixOf) import Data.List(isPrefixOf)
...@@ -304,7 +304,7 @@ takeExtensions = snd . splitExtensions ...@@ -304,7 +304,7 @@ takeExtensions = snd . splitExtensions
-- | Is the given character a valid drive letter? -- | Is the given character a valid drive letter?
-- only a-z and A-Z are letters, not isAlpha which is more unicodey -- only a-z and A-Z are letters, not isAlpha which is more unicodey
isLetter :: Char -> Bool isLetter :: Char -> Bool
isLetter x = (x >= 'a' && x <= 'z') || (x >= 'A' && x <= 'Z') isLetter x = isAsciiLower x || isAsciiUpper x
-- | Split a path into a drive and a path. -- | Split a path into a drive and a path.
...@@ -536,9 +536,7 @@ dropTrailingPathSeparator x = ...@@ -536,9 +536,7 @@ dropTrailingPathSeparator x =
-- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" -- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar"
-- > Windows: takeDirectory "C:\\" == "C:\\" -- > Windows: takeDirectory "C:\\" == "C:\\"
takeDirectory :: FilePath -> FilePath takeDirectory :: FilePath -> FilePath
takeDirectory x = if isDrive file then file takeDirectory x = if isDrive file || (null res && not (null file)) then file else res
else if null res && not (null file) then file
else res
where where
res = reverse $ dropWhile isPathSeparator $ reverse file res = reverse $ dropWhile isPathSeparator $ reverse file
file = dropFileName x file = dropFileName x
...@@ -593,7 +591,7 @@ splitPath x = [drive | drive /= ""] ++ f path ...@@ -593,7 +591,7 @@ splitPath x = [drive | drive /= ""] ++ f path
f y = (a++c) : f d f y = (a++c) : f d
where where
(a,b) = break isPathSeparator y (a,b) = break isPathSeparator y
(c,d) = break (not . isPathSeparator) b (c,d) = span isPathSeparator b
-- | Just as 'splitPath', but don't add the trailing slashes to each element. -- | Just as 'splitPath', but don't add the trailing slashes to each element.
-- --
...@@ -608,7 +606,7 @@ splitDirectories path = ...@@ -608,7 +606,7 @@ splitDirectories path =
where where
pathComponents = splitPath path pathComponents = splitPath path
f xs = map g xs f = map g
g x = if null res then x else res g x = if null res then x else res
where res = takeWhile (not . isPathSeparator) x where res = takeWhile (not . isPathSeparator) x
...@@ -621,7 +619,7 @@ splitDirectories path = ...@@ -621,7 +619,7 @@ splitDirectories path =
-- Note that this definition on c:\\c:\\, join then split will give c:\\. -- Note that this definition on c:\\c:\\, join then split will give c:\\.
joinPath :: [FilePath] -> FilePath joinPath :: [FilePath] -> FilePath
joinPath x = foldr combine "" x joinPath = foldr combine ""
...@@ -799,7 +797,7 @@ makeValid path = joinDrive drv $ validElements $ validChars pth ...@@ -799,7 +797,7 @@ makeValid path = joinDrive drv $ validElements $ validChars pth
where where
(drv,pth) = splitDrive path (drv,pth) = splitDrive path
validChars x = map f x validChars = map f
f x | x `elem` badCharacters = '_' f x | x `elem` badCharacters = '_'
| otherwise = x | otherwise = x
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment