Compare commits

..

9 Commits

Author SHA1 Message Date
bd4f5d7e30 Search endpoints 2019-04-04 08:11:50 +03:00
41806dca67 Remove the irc layout, don't like it 2019-04-02 16:08:05 +03:00
2ad7555b2d Formatting changes 2019-03-21 23:29:39 +02:00
d5c86cddee Enable unstable tests 2019-03-21 22:27:26 +02:00
5041d5bf99 hlint rules 2019-03-21 22:26:47 +02:00
c3d5eaed3e Bump base 2019-03-21 22:19:57 +02:00
164582b9e8 Multiple envs 2019-03-21 22:14:07 +02:00
4b887f7e41 Try out matrix 2019-03-21 22:12:47 +02:00
a680ad1f35 Add tests 2019-03-21 22:09:24 +02:00
7 changed files with 67 additions and 26 deletions

21
.travis.yml Normal file
View File

@ -0,0 +1,21 @@
language: nix
os:
- linux
before_script:
- mkdir -m 0755 -p /nix/var/nix/{profiles,gcroots}/per-user/$USER
- mkdir -p ~/.config/nixpkgs
matrix:
include:
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-18.09.tar.gz
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-19.03.tar.gz
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-unstable.tar.gz
script:
- nix run nixpkgs.haskellPackages.hlint -c hlint src
- nix build -I nixpkgs=$NIXPKGS -f ./release.nix xmonad-masser

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module XMonad.Config.MasseR where
@ -18,7 +19,6 @@ import XMonad.Layout.BinarySpacePartition (emptyBSP)
import XMonad.Layout.Decoration (Decoration,
DefaultShrinker)
import XMonad.Layout.DwmStyle
import XMonad.Layout.HintedGrid
import XMonad.Layout.LayoutModifier (ModifiedLayout)
import XMonad.Layout.Master
import XMonad.Layout.NoBorders (smartBorders)
@ -71,15 +71,17 @@ scratchSubmaps conf = submapName . mkNamedKeymap conf $ [
]
-- Search engines inside submaps
searchSubmaps :: XConfig l -> NamedAction
searchSubmaps conf =
searchSubmaps :: ExtraConfig -> XConfig l -> NamedAction
searchSubmaps extraConfig conf =
let mkBrowser = promptSearchBrowser def "qutebrowser"
_googleP = addName "Search google" $ mkBrowser google
ddgP = addName "Search duckduckgo" $ mkBrowser (searchEngine "duckduckgo" "http://duckduckgo.com/?q=")
extras = [(key, addName name $ mkBrowser (searchEngine name url)) | Search{..} <- searchEndpoints extraConfig]
in submapName . mkNamedKeymap conf $
[ ("d", ddgP) -- Training to use ddg again
, ("g", ddgP) -- training to use ddg again
]
] ++ extras
myNav2d :: Navigation2DConfig
myNav2d = def { defaultTiledNavigation = lineNavigation }
@ -182,9 +184,9 @@ myKeys extraConfig conf =
subKeys "Launchers" [ ("M-S-y", addName "Open youtube" $ spawn "mpv $(clip -o)")
, ("M-S-<Return>", addName "Open terminal" $ spawn $ XMonad.terminal conf)
, ("M-n", scratchSubmaps conf)
, ("M-s", searchSubmaps conf)
, ("M-s", searchSubmaps extraConfig 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)
@ -239,13 +241,11 @@ masser extraConfig = xmonad =<< statusBar (bar extraConfig) zenburnPP toggleStru
onWorkspace "dynamics" webLayout $
onWorkspace "pdf" pdfLayout $
onWorkspace "documents" documentLayout $
onWorkspace "mail" mailLayout $
onWorkspace "irc" ircLayout
onWorkspace "mail" mailLayout
defLayout
where
-- Default layout
defLayout = tiled ||| tabLayout ||| readLayout ||| bspLayout ||| vimLayout ||| spiral (6/7) ||| Full
ircLayout = GridRatio (4/3) False ||| emptyBSP
-- Pdfs are restricted to tabs
vimLayout = Mirror (mastered (1/100) (4/5) Accordion)
pdfLayout = readLayout ||| tiled ||| tabLayout

View File

@ -4,11 +4,29 @@ module XMonad.Config.MasseR.ExtraConfig where
import GHC.Generics (Generic)
import Data.Text (Text)
data Applications = Applications { browser :: FilePath, launcher :: FilePath, prompt :: FilePath, screenshot :: FilePath, urxvt :: FilePath } deriving (Show, Generic)
data Applications =
Applications { browser :: FilePath
, launcher :: FilePath
, prompt :: FilePath
, screenshot :: FilePath
, urxvt :: FilePath
} deriving (Show, Generic)
data TopicRule = TopicRule { topicName :: Text
, topicHome :: Maybe Text
, topicAction :: Maybe Text }
deriving (Show, Generic)
data TopicRule =
TopicRule { topicName :: Text
, topicHome :: Maybe Text
, topicAction :: Maybe Text
}
deriving (Show, Generic)
data ExtraConfig = ExtraConfig { applications :: Applications, topics :: [ TopicRule ] } deriving (Show, Generic)
data Search = Search { name :: String
, key :: String
, url :: String
}
deriving (Show, Generic)
data ExtraConfig =
ExtraConfig { applications :: Applications
, topics :: [ TopicRule ]
, searchEndpoints :: [Search] }
deriving (Show, Generic)

View File

@ -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"

View File

@ -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

View File

@ -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

View File

@ -25,7 +25,7 @@ library
, XMonad.TopicSpace
, XMonad.XMobar
-- other-extensions:
build-depends: base >=4.11 && <4.12
build-depends: base >=4.11 && <4.13
, xmonad
, xmonad-contrib
, mtl