Skip to content

Commit

Permalink
rename historyFetch to historyRead, apply hlint recommendations
Browse files Browse the repository at this point in the history
  • Loading branch information
dcousens committed Jan 18, 2024
1 parent 0c2ad62 commit ef82ecc
Showing 1 changed file with 5 additions and 5 deletions.
10 changes: 5 additions & 5 deletions XMonad/Prompt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,7 +185,7 @@ data XPConfig =
, historyFilter :: [String] -> [String]
-- ^ a filter to determine which
-- history entries to remember
, historyFetch :: FilePath -> IO History
, historyRead :: FilePath -> IO History
-- ^ an IO function for fetching the command history
, historyWrite :: FilePath -> History -> IO ()
-- ^ an IO function for writing the command history
Expand Down Expand Up @@ -348,7 +348,7 @@ instance Default XPConfig where
, maxComplColumns = Nothing
, historySize = 256
, historyFilter = id
, historyFetch = readHistory
, historyRead = readHistory
, historyWrite = writeHistory
, defaultText = []
, autoComplete = Nothing
Expand Down Expand Up @@ -569,7 +569,7 @@ mkXPromptImplementation historyKey conf om = do
s <- gets $ screenRect . W.screenDetail . W.current . windowset
cleanMask <- cleanKeyMask
cachedir <- asks (cacheDir . directories)
hist <- io $ (historyFetch conf) cachedir
hist <- io $ historyRead conf cachedir
fs <- initXMF (font conf)
let width = getWinWidth s (position conf)
st' <- io $
Expand All @@ -589,7 +589,7 @@ mkXPromptImplementation historyKey conf om = do
releaseXMF fs
when (successful st') $ do
let prune = take (historySize conf)
io $ (historyWrite conf) cachedir $
io $ historyWrite conf cachedir $
M.insertWith
(\xs ys -> prune . historyFilter conf $ xs ++ ys)
historyKey
Expand Down Expand Up @@ -1810,7 +1810,7 @@ historyCompletionP p = do
cd <- asks (cacheDir . directories)
pure $ \x ->
let toComplList = deleteConsecutive . filter (isInfixOf x) . M.foldr (++) []
-- in toComplList . M.filterWithKey (const . p) <$> (historyFetch conf) cd
-- in toComplList . M.filterWithKey (const . p) <$> (historyRead conf cd)
in toComplList . M.filterWithKey (const . p) <$> (readHistory cd)

Check warning on line 1814 in XMonad/Prompt.hs

View workflow job for this annotation

GitHub Actions / hlint

Suggestion in historyCompletionP in module XMonad.Prompt: Redundant bracket ▫︎ Found: "toComplList . M.filterWithKey (const . p) <$> (readHistory cd)" ▫︎ Perhaps: "toComplList . M.filterWithKey (const . p) <$> readHistory cd"

-- | Sort a list and remove duplicates. Like 'deleteAllDuplicates', but trades off
Expand Down

0 comments on commit ef82ecc

Please sign in to comment.