summaryrefslogtreecommitdiffstats
path: root/src/XMonad/Local/Layout.hs
blob: 4b3d789e947272bc566cb847a59171a4cc326873 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
{-# OPTIONS -fno-warn-missing-signatures #-}
{-# LANGUAGE FlexibleContexts #-}

module XMonad.Local.Layout (layoutHook) where

import Data.Ratio ((%))
import XMonad.Hooks.ManageDocks (avoidStruts)
import XMonad.Layout
import XMonad.Layout.Accordion
import qualified XMonad.Layout.BoringWindows as BW
import XMonad.Layout.Column
import qualified XMonad.Layout.ComboP as CP
import qualified XMonad.Layout.IM as IM
import qualified XMonad.Layout.MultiToggle as MT
import qualified XMonad.Layout.Named as LN
import XMonad.Layout.NoBorders
import qualified XMonad.Layout.PerWorkspace as PW
import XMonad.Layout.Reflect
import XMonad.Layout.SimpleFloat
import XMonad.Layout.Simplest (Simplest(..))
import XMonad.Layout.SubLayouts
import qualified XMonad.Layout.Tabbed as Tab
import XMonad.Layout.ThreeColumns
import XMonad.Layout.ToggleLayouts
import XMonad.Layout.TrackFloating
import XMonad.Layout.TwoPane
import XMonad.Layout.WindowNavigation

-- local modules **************************************************************
import XMonad.Layout.TopicDir as TD
import XMonad.Local.TopicSpace as Local

layoutHook = avoidStruts
           $ TD.topicDir Local.topicDirs
           $ PW.onWorkspace "chat" chatL
           $ PW.onWorkspace "gimp" gimpL
           $ PW.onWorkspace "BG" bgL
           $ PW.onWorkspace "witcher" witcherL
           $ PW.onWorkspace "remote" remoteL
           $ PW.onWorkspaces ["homam5", "civ4", "pst", "ciV"] wineGameL
             easyLay

nmaster = 1
ratio = 1/2
delta = 3/100

tiled =  Tall nmaster delta ratio
threecol =  ThreeColMid nmaster delta (1/3)

-- common layouts
easyLay = windowNavigation baseLay 
baseLay = smartBorders (tiled' ||| tabbed')
    where
        tiled' = mySubTabbed $ BW.boringWindows
               $ toggleLayouts threecol
               $       MT.mkToggle (MT.single REFLECTX) tiled
                   ||| MT.mkToggle (MT.single REFLECTY) (Mirror tiled)
        tabbed' = BW.boringWindows $ trackFloating $ Tab.tabbed Tab.shrinkText myTabTheme


-- workspace layouts
chatL = IM.withIM (1%5) (IM.ClassName "Skype"
             `IM.And`   (        IM.Title "minarmc - Skype™ (Beta)"
                        `IM.Or`  IM.Title "Skype™ 2.2 (Beta) for Linux"
                        `IM.Or`  IM.Title "minarmc - Skype™"))
      $ IM.withIM (1%5) (        IM.ClassName "Empathy"
                        `IM.And` (IM.Title "Contact List" `IM.Or` IM.Role "contact_list"))
        easyLay

gimpL = LN.named "GIMP"
      $ windowNavigation
      $ smartBorders
      $ IM.withIM (11/64) (IM.Role "gimp-toolbox")
      $ CP.combineTwoP
            (reflectHoriz $ TwoPane delta 0.2)
            (Column 0)
            (mySubTabbed $ BW.boringWindows Accordion)
            (        CP.ClassName "Gimp"
            `CP.And` CP.Not (CP.Role "gimp-image-window"))

bgL = windowNavigation $ BW.boringWindows $ smartBorders
    $ reflectHoriz $ Tall nmaster delta (7/9)

witcherL = windowNavigation $ BW.boringWindows $ noBorders
    $ IM.withIM (2%7) (IM.ClassName "Firefox") tiled

remoteL = windowNavigation $ BW.boringWindows $ smartBorders
        $ Tab.tabbed Tab.shrinkText myTabTheme

wineGameL = smartBorders $ simpleFloat ||| trackFloating Full

mySubTabbed x = trackFloating $ Tab.addTabs Tab.shrinkText myTabTheme $ subLayout [] Simplest x

myTabTheme :: Tab.Theme
myTabTheme = Tab.def
    { Tab.activeTextColor     = "#ffffff"
    , Tab.activeBorderColor   = "#FBAB2E"
    , Tab.activeColor         = "#3c3c3c"
    , Tab.inactiveTextColor   = "#c0c0c0"
    , Tab.inactiveBorderColor = "#c0c0c0"
    , Tab.inactiveColor       = "#3c3c3c"
    , Tab.urgentTextColor     = "#ff0000"
    , Tab.urgentBorderColor   = "#ff0000"
    , Tab.urgentColor         = "#000000"
    , Tab.fontName            = "-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*"
    , Tab.decoHeight          = 24
    }