hlint rules
This commit is contained in:
		@@ -184,7 +184,7 @@ myKeys extraConfig conf =
 | 
			
		||||
                        , ("M-n", scratchSubmaps conf)
 | 
			
		||||
                        , ("M-s", searchSubmaps conf)
 | 
			
		||||
                        , ("M-p", addName "Retrieve password" $ passPrompt def)
 | 
			
		||||
                        , ("M-S-e", addName "Open with app" xdg_open)
 | 
			
		||||
                        , ("M-S-e", addName "Open with app" xdgOpen)
 | 
			
		||||
                        , ("M-e", addName "Run app" $ runOrRaisePrompt def)] ^++^
 | 
			
		||||
    subKeys "Windows" [ ("M-j", addName "Go down" $ windowGo D False)
 | 
			
		||||
                      , ("M-k", addName "Go up" $ windowGo U False)
 | 
			
		||||
 
 | 
			
		||||
@@ -1,4 +1,4 @@
 | 
			
		||||
module XMonad.CustomPrompt (xdg_open, browser) where
 | 
			
		||||
module XMonad.CustomPrompt (xdgOpen, browser) where
 | 
			
		||||
 | 
			
		||||
import qualified XMonad.Prompt.AppLauncher as AL
 | 
			
		||||
import XMonad.Prompt
 | 
			
		||||
@@ -7,8 +7,8 @@ import XMonad (X)
 | 
			
		||||
launchApp ::  AL.Application -> X ()
 | 
			
		||||
launchApp = AL.launchApp def
 | 
			
		||||
 | 
			
		||||
xdg_open :: X ()
 | 
			
		||||
xdg_open = launchApp "xdg-open"
 | 
			
		||||
xdgOpen :: X ()
 | 
			
		||||
xdgOpen = launchApp "xdg-open"
 | 
			
		||||
 | 
			
		||||
browser :: X ()
 | 
			
		||||
browser = launchApp "qutebrowser"
 | 
			
		||||
 
 | 
			
		||||
@@ -10,7 +10,7 @@ import           XMonad.Core
 | 
			
		||||
import           XMonad.Prompt
 | 
			
		||||
import           XMonad.Util.Run       (runProcessWithInput)
 | 
			
		||||
 | 
			
		||||
data Pass = Pass { passLabel :: String }
 | 
			
		||||
newtype Pass = Pass { passLabel :: String }
 | 
			
		||||
 | 
			
		||||
-- Rosetta code levenshtein
 | 
			
		||||
levenshtein :: String -> String -> Int
 | 
			
		||||
@@ -37,7 +37,7 @@ mkPassPrompt label f conf = do
 | 
			
		||||
  -- I'm just sorting here, but could use some kind of fuzzy matching instead, but it requires a bit more effort
 | 
			
		||||
  passwords <- sort <$> liftIO getPasswords
 | 
			
		||||
  -- Other change, use infixof instead of prefixof
 | 
			
		||||
  mkXPrompt (Pass label) conf (\input -> pure (sortBy (compare `on` (levenshtein input)) . filter (consumes input) $ passwords)) f
 | 
			
		||||
  mkXPrompt (Pass label) conf (\input -> pure (sortBy (compare `on` levenshtein input) . filter (consumes input) $ passwords)) f
 | 
			
		||||
  where
 | 
			
		||||
    consumes [] _ = True -- everything consumed
 | 
			
		||||
    consumes (_:_) [] = False -- all not consumed
 | 
			
		||||
 
 | 
			
		||||
@@ -1,7 +1,8 @@
 | 
			
		||||
{-# LANGUAGE TupleSections #-}
 | 
			
		||||
module XMonad.TopicUtils where
 | 
			
		||||
 | 
			
		||||
import Data.Maybe (fromMaybe, listToMaybe, mapMaybe)
 | 
			
		||||
import Data.List (isPrefixOf, sort, nub)
 | 
			
		||||
import Data.List (isPrefixOf, nub, sortOn)
 | 
			
		||||
import XMonad.Actions.TopicSpace
 | 
			
		||||
import XMonad
 | 
			
		||||
import qualified Data.Map as M
 | 
			
		||||
@@ -11,6 +12,7 @@ import qualified XMonad.StackSet as W
 | 
			
		||||
import XMonad.Util.Dmenu (dmenu)
 | 
			
		||||
import XMonad.Actions.DynamicWorkspaces
 | 
			
		||||
import XMonad.Util.NamedWindows (getName)
 | 
			
		||||
import Data.Ord
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
realTopicDir :: M.Map String FilePath -> X String
 | 
			
		||||
@@ -58,7 +60,7 @@ gridselectCurrentWindows :: GSConfig Window -> X (Maybe Window)
 | 
			
		||||
gridselectCurrentWindows gsconf = windowMap >>= gridselect gsconf
 | 
			
		||||
    where
 | 
			
		||||
        getName' = fmap show . getName
 | 
			
		||||
        kvPair w = flip (,) w `fmap` getName' w
 | 
			
		||||
        kvPair w = (, w) <$> getName' w
 | 
			
		||||
        windowMap = do
 | 
			
		||||
            ws <- gets (nub . W.integrate' . W.stack . W.workspace . W.current . windowset)
 | 
			
		||||
            mapM kvPair ws
 | 
			
		||||
@@ -78,11 +80,11 @@ currentTopicAction' tg = do
 | 
			
		||||
copyTopic :: X ()
 | 
			
		||||
copyTopic = do
 | 
			
		||||
  currentTopic <- realTopic
 | 
			
		||||
  lastN <- gets (listToMaybe . reverse . sort . mapMaybe (subset currentTopic . W.tag) . W.workspaces . windowset)
 | 
			
		||||
  addWorkspace (currentTopic ++ ":" ++ (show $ maybe 2 (+1) lastN))
 | 
			
		||||
  lastN <- gets (listToMaybe . sortOn Down . mapMaybe (subset currentTopic . W.tag) . W.workspaces . windowset)
 | 
			
		||||
  addWorkspace (currentTopic ++ ":" ++ show (maybe 2 (+1) lastN))
 | 
			
		||||
  where
 | 
			
		||||
    subset :: String -> String -> Maybe Int
 | 
			
		||||
    subset topic other = if topic `isPrefixOf` other then (readM $ tail' $ snd $ break (== ':') other) else Nothing
 | 
			
		||||
    subset topic other = if topic `isPrefixOf` other then readM $ tail' $ dropWhile (/= ':') other else Nothing
 | 
			
		||||
    readM a = case reads a of
 | 
			
		||||
               [(x,_)] -> Just x
 | 
			
		||||
               _ -> Nothing
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user