Skip to content

Commit

Permalink
apply hlint suggestions
Browse files Browse the repository at this point in the history
  • Loading branch information
Tom Sydney Kerckhove committed Aug 11, 2024
1 parent 053a1fb commit b64dd04
Show file tree
Hide file tree
Showing 7 changed files with 18 additions and 15 deletions.
4 changes: 4 additions & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
- ignore:
name: "Redundant if"
- ignore:
name: "Use unless"
1 change: 1 addition & 0 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@
nixpkgs-fmt.enable = true;
nixpkgs-fmt.excludes = [ ".*/default.nix" ];
deadnix.enable = true;
hlint.enable = true;
cabal2nix.enable = true;
};
};
Expand Down
21 changes: 10 additions & 11 deletions path/src/Path/Include.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}

module Path.PLATFORM_NAME
(-- * Types
Expand Down Expand Up @@ -103,7 +102,7 @@ module Path.PLATFORM_NAME
import Control.Applicative (Alternative(..))
import Control.DeepSeq (NFData (..))
import Control.Exception (Exception(..))
import Control.Monad (liftM, when)
import Control.Monad (when)
import Control.Monad.Catch (MonadThrow(..))
import Data.Aeson (FromJSON (..), FromJSONKey(..), ToJSON(..))
import qualified Data.Aeson.Types as Aeson
Expand Down Expand Up @@ -462,10 +461,10 @@ dirname (Path l) = Path (last (FilePath.splitPath l))
-- @since 0.7.0
splitExtension :: MonadThrow m => Path b File -> m (Path b File, String)
splitExtension (Path fpath) =
if nameDot == [] || ext == []
if null nameDot || null ext
then throwM $ HasNoExtension fpath
else let fname = init nameDot
in if fname == [] || fname == "." || fname == ".."
in if null fname || fname == "." || fname == ".."
then throwM $ HasNoExtension fpath
else return ( Path (normalizeDrive drv ++ dir ++ fname)
, FilePath.extSeparator : ext
Expand Down Expand Up @@ -499,7 +498,7 @@ splitExtension (Path fpath) =
--
-- @since 0.5.11
fileExtension :: MonadThrow m => Path b File -> m String
fileExtension = (liftM snd) . splitExtension
fileExtension = fmap snd . splitExtension

-- | Add extension to given file path.
--
Expand Down Expand Up @@ -541,7 +540,7 @@ addExtension ext (Path path) = do
throwM $ InvalidExtension ex

-- just a "." is not a valid extension
when (xs == []) $
when (null xs) $
throwM $ InvalidExtension ex

-- cannot have path separators
Expand All @@ -550,7 +549,7 @@ addExtension ext (Path path) = do

-- All "."s is not a valid extension
let ys = dropWhile FilePath.isExtSeparator (reverse xs)
when (ys == []) $
when (null ys) $
throwM $ InvalidExtension ex

-- Cannot have "."s except in trailing position
Expand Down Expand Up @@ -586,8 +585,8 @@ addFileExtension :: MonadThrow m
-> m (Path b File) -- ^ New file name with the desired extension added at the end
addFileExtension ext (Path path) =
if FilePath.isAbsolute path
then liftM coercePath (parseAbsFile (FilePath.addExtension path ext))
else liftM coercePath (parseRelFile (FilePath.addExtension path ext))
then fmap coercePath (parseAbsFile (FilePath.addExtension path ext))
else fmap coercePath (parseRelFile (FilePath.addExtension path ext))
where coercePath :: Path a b -> Path a' b'
coercePath (Path a) = Path a

Expand Down Expand Up @@ -636,8 +635,8 @@ setFileExtension :: MonadThrow m
-> m (Path b File) -- ^ New file name with the desired extension
setFileExtension ext (Path path) =
if FilePath.isAbsolute path
then liftM coercePath (parseAbsFile (FilePath.replaceExtension path ext))
else liftM coercePath (parseRelFile (FilePath.replaceExtension path ext))
then fmap coercePath (parseAbsFile (FilePath.replaceExtension path ext))
else fmap coercePath (parseRelFile (FilePath.replaceExtension path ext))
where coercePath :: Path a b -> Path a' b'
coercePath (Path a) = Path a

Expand Down
1 change: 0 additions & 1 deletion path/test-ospath/Common/Include.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}

-- | Test functions that are common to Posix and Windows
module Common.PLATFORM_NAME
Expand Down
2 changes: 1 addition & 1 deletion path/test/Posix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ aesonInstances =
it "Decoding \"[\"/foo/bar\"]\" as a [Path Rel Dir] should fail." $
decode (LBS.pack "[\"/foo/bar\"]") `shouldBe` (Nothing :: Maybe [Path Rel Dir])
it "Encoding \"[\"/foo/bar/mu.txt\"]\" should succeed." $
encode [Path "/foo/bar/mu.txt" :: Path Abs File] `shouldBe` (LBS.pack "[\"/foo/bar/mu.txt\"]")
encode [Path "/foo/bar/mu.txt" :: Path Abs File] `shouldBe` LBS.pack "[\"/foo/bar/mu.txt\"]"

-- | Test QuasiQuoters. Make sure they work the same as the $(mk*) constructors.
quasiquotes :: Spec
Expand Down
2 changes: 1 addition & 1 deletion path/test/Windows.hs
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ aesonInstances =
it "Decoding \"[\"C:\\foo\\bar\"]\" as a [Path Rel Dir] should fail." $
decode (LBS.pack "[\"C:\\foo\\bar\"]") `shouldBe` (Nothing :: Maybe [Path Rel Dir])
it "Encoding \"[\"C:\\foo\\bar\\mu.txt\"]\" should succeed." $
encode [Path "C:\\foo\\bar\\mu.txt" :: Path Abs File] `shouldBe` (LBS.pack "[\"C:\\\\foo\\\\bar\\\\mu.txt\"]")
encode [Path "C:\\foo\\bar\\mu.txt" :: Path Abs File] `shouldBe` LBS.pack "[\"C:\\\\foo\\\\bar\\\\mu.txt\"]"

-- | Test QuasiQuoters. Make sure they work the same as the $(mk*) constructors.
quasiquotes :: Spec
Expand Down
2 changes: 1 addition & 1 deletion path/validity-test/Path/Gen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -123,4 +123,4 @@ genPathyChar :: Gen Char
genPathyChar = frequency [(2, choose (minBound, maxBound)), (1, elements "./\\")]

shrinkValidWith :: (FilePath -> Maybe (Path a b)) -> Path a b -> [Path a b]
shrinkValidWith fun (Path f) = filter (/= (Path f)) . mapMaybe fun $ shrinkValid f
shrinkValidWith fun (Path f) = filter (/= Path f) . mapMaybe fun $ shrinkValid f

0 comments on commit b64dd04

Please sign in to comment.