diff --git a/src/XMonad/Config.hs b/src/XMonad/Config.hs deleted file mode 100644 index 7ed6699..0000000 --- a/src/XMonad/Config.hs +++ /dev/null @@ -1,36 +0,0 @@ -{-# Language RecordWildCards #-} -{-# Language DeriveGeneric #-} -{-# Language OverloadedStrings #-} -module Config where - -import Dhall - -data Applications = Applications { urxvt :: Text - , prompt :: Text - , browser :: Text - , launcher :: Text -- xdg-open - , screenshot :: 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) - -defaultExtraConfig :: ExtraConfig -defaultExtraConfig = - let applications = Applications{..} - urxvt = "urxvt" - prompt = "xmobar" - browser = "qutebrowser" - launcher = "xdg-open" - screenshot = "scrot ~/screenSel.png" - topics = [] - in ExtraConfig{..} - -instance Interpret ExtraConfig -instance Interpret TopicRule -instance Interpret Applications diff --git a/src/XMonad/Customizations.hs b/src/XMonad/Customizations.hs deleted file mode 100644 index 73923a7..0000000 --- a/src/XMonad/Customizations.hs +++ /dev/null @@ -1,21 +0,0 @@ -{-# Language FlexibleContexts #-} -module Customizations (customizations) where - -import Configurable -import XMonad -import XMonad.Util.EZConfig (additionalKeys) - -import Customizations.Types -import qualified Customizations.Topics as Topics - -import Control.Lens - -customizations :: LayoutClass l Window => XConfig l -> XConfig l -customizations start = xconfig $ configure (mconcat [topics, Topics.customize, initial]) - where - initial = EndoM $ \_ -> pure (Customize start def) - topics :: LayoutClass l Window => Configurable (Customize l) - topics = EndoM $ \super -> do - _self <- ask - pure (over _xconfig _ super) - diff --git a/src/XMonad/Projects.hs b/src/XMonad/Projects.hs deleted file mode 100644 index 8cab02e..0000000 --- a/src/XMonad/Projects.hs +++ /dev/null @@ -1 +0,0 @@ -module Projects where diff --git a/src/XMonad/RestartFile.hs b/src/XMonad/RestartFile.hs deleted file mode 100644 index d9830da..0000000 --- a/src/XMonad/RestartFile.hs +++ /dev/null @@ -1,47 +0,0 @@ -module RestartFile (restartFile, resumeArgsFromFile, getArgs, withArgs) where - -import XMonad.Core -import XMonad.Operations -import qualified XMonad.StackSet as W -import Graphics.X11.Xlib.Event -import Control.Monad.Reader (asks) -import Control.Monad.State (gets) -import Data.Maybe -import Data.List (intercalate) -import qualified Data.Map.Strict as M -import System.Environment (getArgs, withArgs) -import Control.Monad -import Control.Exception -import System.Posix.Process (executeFile) - -stateFile = "xmonadargs.txt" - -restartFile :: String -> Bool -> X () -restartFile prog resume = do - io $ appendFile "/home/masse/xmonad.log" $ "trying to restart" - broadcastMessage ReleaseResources - io . flush =<< asks display - let wsData = show . W.mapLayout show . windowset - maybeShow (t, Right (PersistentExtension ext)) = Just (t, show ext) - maybeShow (t, Left str) = Just (t, str) - maybeShow _ = Nothing - extState = return . show . mapMaybe maybeShow . M.toList . extensibleState - args <- if resume then return ["--resume"] else return [] - when resume $ do - argsstr <- gets (\s -> intercalate "\n" ("--resume":wsData s:extState s)) - catchIO $ writeFile stateFile argsstr - return () - catchIO (executeFile prog True args Nothing) - -catchAny :: IO a -> (SomeException -> IO a) -> IO a -catchAny = Control.Exception.catch - -resumeArgsFromFile :: IO [String] -resumeArgsFromFile = do - let readLines = liftM lines . readFile $ stateFile - args <- getArgs - if ["--resume"] == args then - catchAny readLines $ \e -> do - appendFile "/home/masse/xmonad.log" $ "got error" ++ show e - return args - else return args diff --git a/src/XMonad/Screen.hs b/src/XMonad/Screen.hs deleted file mode 100644 index f87c67e..0000000 --- a/src/XMonad/Screen.hs +++ /dev/null @@ -1,38 +0,0 @@ -module Screen (screenWidth, nextScreen, prevScreen) where - -import Graphics.X11.Xinerama (xineramaQueryScreens, XineramaScreenInfo(..)) -import Graphics.X11.Xlib (openDisplay, closeDisplay) -import qualified XMonad.Actions.CycleWS as CycleWS -import XMonad (X()) -import Control.Monad.Trans (liftIO) - -screenWidth :: Int -> IO Int -screenWidth idx = do - dsp <- openDisplay "" -- I don't know what the string does :/ - info <- xineramaQueryScreens dsp - case info of - Nothing -> return 0 - Just [] -> return 0 - Just screens -> if idx >= 0 && idx < length screens - then (return . fromIntegral . xsi_width) (screens !! idx) - else return 0 - -swapScreenDir :: IO Bool -swapScreenDir = do - dsp <- openDisplay "" - info <- xineramaQueryScreens dsp - closeDisplay dsp - case info of - Nothing -> return False - Just [] -> return False - Just (s:_) -> return (xsi_width s > 0) - -nextScreen :: X () -nextScreen = do - swap <- liftIO $ swapScreenDir -- Not too fond of querying the x each time we swap screens, but oh well - if swap then CycleWS.prevScreen else CycleWS.nextScreen - -prevScreen :: X () -prevScreen = do - swap <- liftIO $ swapScreenDir -- Not too fond of querying the x each time we swap screens, but oh well - if swap then CycleWS.nextScreen else CycleWS.prevScreen diff --git a/src/XMonad/TreeSelectUtils.hs b/src/XMonad/TreeSelectUtils.hs deleted file mode 100644 index c60fd33..0000000 --- a/src/XMonad/TreeSelectUtils.hs +++ /dev/null @@ -1,20 +0,0 @@ -module TreeSelectUtils where - -import XMonad.Actions.TreeSelect -import Data.Tree -import Data.List (sort, groupBy) -import Data.Function (on) -import qualified XMonad.StackSet as W -import XMonad.Core -import Control.Monad.State - --- fromWorkspace :: [String] -> Forest String -fromWorkspace = map go . group . sort - where - group = groupBy ((==) `on` (takeWhile (/= '.'))) - go (root:xs) = Node root [Node x [] | x <- xs] - -treeselectWorkspaces' conf f = withWindowSet $ \w -> do - let ws = map W.tag . W.hidden $ w - treeselectWorkspace conf (fromWorkspace ws) f -