mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
make xmonad work with inverted main/config.
This commit is contained in:
parent
97fe14dfd2
commit
7b3c1243b7
@ -39,7 +39,7 @@ import System.IO
|
|||||||
--
|
--
|
||||||
makeMain :: String -> String -> Layout Window -> [String] -> [(Int,Int,Int,Int)]
|
makeMain :: String -> String -> Layout Window -> [String] -> [(Int,Int,Int,Int)]
|
||||||
-> M.Map (ButtonMask,KeySym) (X ()) -> M.Map (ButtonMask, Button) (Window -> X ())
|
-> M.Map (ButtonMask,KeySym) (X ()) -> M.Map (ButtonMask, Button) (Window -> X ())
|
||||||
-> Int -> X () -> IO ()
|
-> Dimension -> X () -> IO ()
|
||||||
makeMain normalBorderColor focusedBorderColor layoutHook workspaces
|
makeMain normalBorderColor focusedBorderColor layoutHook workspaces
|
||||||
defaultGaps keys mouseBindings borderWidth logHook = do
|
defaultGaps keys mouseBindings borderWidth logHook = do
|
||||||
dpy <- openDisplay ""
|
dpy <- openDisplay ""
|
||||||
|
@ -14,7 +14,7 @@
|
|||||||
--
|
--
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
module Main ( main ) where
|
module Main where
|
||||||
|
|
||||||
--
|
--
|
||||||
-- Useful imports
|
-- Useful imports
|
||||||
@ -277,5 +277,6 @@ mouseBindings = M.fromList $
|
|||||||
|
|
||||||
-- % The main function
|
-- % The main function
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
main = makeMain normalBorderColor focusedBorderColor layoutHook workspaces
|
main = makeMain normalBorderColor focusedBorderColor layoutHook workspaces
|
||||||
defaultGaps keys mouseBindings borderWidth logHook
|
defaultGaps keys mouseBindings borderWidth logHook
|
@ -1,4 +1,4 @@
|
|||||||
module Config where
|
module Main where
|
||||||
import Graphics.X11.Xlib.Types (Dimension)
|
import Graphics.X11.Xlib.Types (Dimension)
|
||||||
import Graphics.X11.Xlib (KeyMask,Window)
|
import Graphics.X11.Xlib (KeyMask,Window)
|
||||||
import XMonad
|
import XMonad
|
@ -20,7 +20,6 @@ module Operations where
|
|||||||
|
|
||||||
import XMonad
|
import XMonad
|
||||||
import qualified StackSet as W
|
import qualified StackSet as W
|
||||||
import {-# SOURCE #-} Config (borderWidth,logHook,manageHook,numlockMask,serialisedLayouts)
|
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.List (nub, (\\), find, partition)
|
import Data.List (nub, (\\), find, partition)
|
||||||
@ -38,6 +37,8 @@ import Graphics.X11.Xlib
|
|||||||
import Graphics.X11.Xinerama (getScreenInfo)
|
import Graphics.X11.Xinerama (getScreenInfo)
|
||||||
import Graphics.X11.Xlib.Extras
|
import Graphics.X11.Xlib.Extras
|
||||||
|
|
||||||
|
import {-# SOURCE #-} Main (borderWidth,logHook,manageHook,numlockMask,serialisedLayouts)
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Window manager operations
|
-- Window manager operations
|
||||||
|
@ -22,7 +22,7 @@ extra-source-files: README TODO tests/loc.hs tests/Properties.hs man/xmonad.1.in
|
|||||||
Config.hs-boot util/GenerateManpage.hs man/xmonad.1 man/xmonad.html
|
Config.hs-boot util/GenerateManpage.hs man/xmonad.1 man/xmonad.html
|
||||||
|
|
||||||
executable: xmonad
|
executable: xmonad
|
||||||
main-is: config.hs
|
main-is: Main.hs
|
||||||
other-modules: EventLoop Operations StackSet XMonad
|
other-modules: EventLoop Operations StackSet XMonad
|
||||||
ghc-options: -funbox-strict-fields -O2 -fasm -Wall -optl-Wl,-s
|
ghc-options: -funbox-strict-fields -O2 -fasm -Wall -optl-Wl,-s
|
||||||
ghc-prof-options: -prof -auto-all
|
ghc-prof-options: -prof -auto-all
|
||||||
|
Loading…
x
Reference in New Issue
Block a user