Compare commits

...

3 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
2 changed files with 32 additions and 14 deletions

View File

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

View File

@ -4,11 +4,29 @@ module XMonad.Config.MasseR.ExtraConfig where
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Text (Text) 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 data TopicRule =
, topicHome :: Maybe Text TopicRule { topicName :: Text
, topicAction :: Maybe Text } , topicHome :: Maybe Text
deriving (Show, Generic) , 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)