Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.

Commit 23df12a

Browse files
author
Patrick Thomson
authored
Merge pull request #159 from jhrcek/fixHlintWarnings
Fix some hlint warnings
2 parents 02e56c9 + ade8e8b commit 23df12a

File tree

19 files changed

+58
-56
lines changed

19 files changed

+58
-56
lines changed

.hlint.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,7 @@
6767
# Conveniences
6868
- warning: {lhs: maybe a pure, rhs: maybeM a, name: Use maybeM}
6969
- warning: {lhs: either (const a) id, rhs: fromRight a, name: use fromRight}
70-
- warning: {lhs: either id (const a), rhs: fromLeft a, name: use fromRight}
70+
- warning: {lhs: either id (const a), rhs: fromLeft a, name: use fromLeft}
7171

7272
# Applicative style
7373
- warning: {lhs: f <$> pure a <*> b, rhs: f a <$> b, name: Avoid redundant pure}

semantic-core/src/Analysis/Concrete.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
1+
{-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, RecordWildCards, TypeOperators, UndecidableInstances #-}
22
module Analysis.Concrete
33
( Concrete(..)
44
, concrete

semantic-core/src/Analysis/Eval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE FlexibleContexts, GeneralizedNewtypeDeriving, LambdaCase, RankNTypes, RecordWildCards #-}
1+
{-# LANGUAGE FlexibleContexts, LambdaCase, RankNTypes, RecordWildCards #-}
22
module Analysis.Eval
33
( eval
44
, prog1

semantic-core/src/Analysis/Typecheck.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,7 @@ typecheckingAnalysis = Analysis{..}
160160
bool _ = pure MBool
161161
asBool b = unify MBool b >> pure True <|> pure False
162162
string _ = pure MString
163-
asString s = unify MString s *> pure ""
163+
asString s = unify MString s $> ""
164164
frame = fail "unimplemented"
165165
edge _ _ = pure ()
166166
_ ... m = m

semantic-core/src/Control/Effect/Readline.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ instance (Carrier sig m, Effect sig, MonadException m, MonadIO m) => Carrier (Re
8181

8282
runReadlineWithHistory :: MonadException m => ReadlineC m a -> m a
8383
runReadlineWithHistory block = do
84-
homeDir <- liftIO $ getHomeDirectory
84+
homeDir <- liftIO getHomeDirectory
8585
prefs <- liftIO $ readPrefs (homeDir </> ".haskeline")
8686
let settingsDir = homeDir </> ".local/semantic-core"
8787
settings = Settings

semantic-core/test/Spec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE OverloadedStrings, TypeApplications #-}
1+
{-# LANGUAGE OverloadedStrings #-}
22
{-# OPTIONS_GHC -fno-warn-orphans #-}
33

44
module Main (main) where

src/Data/Language.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures, LambdaCase #-}
1+
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures #-}
22
module Data.Language
33
( Language (..)
44
, SLanguage (..)

src/Data/Project.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE DeriveAnyClass, KindSignatures, MultiWayIf #-}
1+
{-# LANGUAGE DeriveAnyClass, MultiWayIf #-}
22

33
module Data.Project
44
( Project (..)

src/Semantic/Git.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ import Control.Monad.IO.Class
1919
import Data.Attoparsec.Text (Parser)
2020
import Data.Attoparsec.Text as AP
2121
import Data.Char
22+
import Data.Either (fromRight)
2223
import Data.Text as Text
2324
import Shelly hiding (FilePath)
2425
import System.IO (hSetBinaryMode)
@@ -42,7 +43,7 @@ sh = shelly . silently . onCommandHandles (initOutputHandles (`hSetBinaryMode` T
4243

4344
-- | Parses an list of entries separated by \NUL, and on failure return []
4445
parseEntries :: Text -> [TreeEntry]
45-
parseEntries = either (const []) id . AP.parseOnly everything
46+
parseEntries = fromRight [] . AP.parseOnly everything
4647
where
4748
everything = AP.sepBy entryParser "\NUL" <* "\NUL\n" <* AP.endOfInput
4849

@@ -87,4 +88,3 @@ data TreeEntry
8788
, treeEntryOid :: OID
8889
, treeEntryPath :: FilePath
8990
} deriving (Eq, Show)
90-

src/Tags/Taggable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,7 @@ instance Taggable Expression.Call where
189189
instance Taggable Ruby.Send where
190190
snippet ann (Ruby.Send _ _ _ (Just (Term (In body _)))) = Just $ subtractLocation ann body
191191
snippet ann _ = Just $ locationByteRange ann
192-
symbolName Ruby.Send{..} = maybe Nothing declaredName sendSelector
192+
symbolName Ruby.Send{..} = declaredName =<< sendSelector
193193

194194
instance Taggable []
195195
instance Taggable Comment.Comment

0 commit comments

Comments
 (0)