-
-
Save ronin13/a63243e5e906f7f8802c to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE NoMonomorphismRestriction #-} | |
--{{{ Imports | |
import XMonad.Layout.Gaps | |
import XMonad.Actions.WindowBringer | |
import XMonad.Actions.FindEmptyWorkspace | |
import XMonad.Util.WorkspaceCompare | |
import XMonad hiding ( (|||) ) | |
import XMonad.Hooks.InsertPosition | |
import XMonad.Actions.NoBorders | |
import XMonad.Hooks.FadeWindows | |
import XMonad.Hooks.FadeInactive | |
import XMonad.Layout.HintedTile as HT | |
{-import Graphics.X11.Xlib.Extras as Ex-} | |
{-import Monad-} | |
import Data.Monoid | |
import XMonad.Util.Dmenu | |
import XMonad.Hooks.UrgencyHook | |
import XMonad.Actions.WindowGo | |
import XMonad.Util.Loggers | |
import System.Exit | |
import XMonad.Hooks.DynamicLog | |
import XMonad.Layout.ResizableTile | |
import XMonad.Layout.Magnifier | |
import XMonad.Hooks.ManageDocks | |
import XMonad.Actions.OnScreen | |
{-import XMonad.Util.Scratchpad (scratchpadSpawnActionCustom)-} | |
import XMonad.Actions.CopyWindow | |
import XMonad.Hooks.EwmhDesktops | |
import XMonad.Layout.LayoutHints | |
import XMonad.Hooks.ManageHelpers | |
import XMonad.Actions.SinkAll | |
import XMonad.Util.Types | |
import XMonad.Layout.Tabbed | |
import XMonad.Prompt | |
import XMonad.Prompt.Window | |
import XMonad.Prompt.XMonad | |
import XMonad.Prompt.Theme | |
import XMonad.Prompt.Workspace | |
import XMonad.Prompt.Man | |
import XMonad.Prompt.AppendFile | |
import XMonad.Prompt.RunOrRaise | |
import XMonad.Prompt.Ssh | |
import XMonad.Actions.SpawnOn | |
import XMonad.Actions.GridSelect | |
import XMonad.Actions.CycleRecentWS | |
import XMonad.Prompt.Shell | |
import XMonad.Hooks.SetWMName | |
import XMonad.Hooks.ServerMode | |
import XMonad.Actions.Commands | |
import XMonad.Layout.StackTile | |
import Data.List as L | |
import XMonad.Actions.Navigation2D | |
{-import XMonad.Hooks.InsertPosition-} | |
import XMonad.Layout.NoBorders | |
import XMonad.Layout.PerWorkspace (onWorkspace) | |
import XMonad.Layout.LayoutCombinators | |
import XMonad.Util.Run(spawnPipe) | |
import XMonad.Util.EZConfig | |
import System.IO | |
import XMonad.Actions.CycleWS | |
import XMonad.Layout.MultiToggle as T | |
import XMonad.Layout.MultiToggle.Instances | |
{-import qualified XMonad.Layout.Fullscreen as F-} | |
import XMonad.Layout.DecorationMadness | |
import XMonad.Prompt.Theme | |
import qualified XMonad.StackSet as W | |
import qualified Data.Map as M | |
import qualified XMonad.Layout.Magnifier as Mag | |
import XMonad.Actions.GroupNavigation as G | |
import XMonad.Hooks.Minimize | |
import XMonad.Layout.Minimize | |
import XMonad.Layout.BoringWindows as BW | |
import XMonad.Layout.Simplest | |
import XMonad.Util.NamedScratchpad | |
--}}} | |
myTabConfig = defaultTheme { activeColor = "#333333" | |
, inactiveColor = "#333333" | |
, activeBorderColor = "#285577" | |
, inactiveBorderColor = "#222222" | |
, activeTextColor = "#ffffff" | |
, inactiveTextColor = "#888888" | |
, fontName = "xft:Liberation Mono-8" | |
, decoHeight = 16 } | |
myXPConfig = defaultXPConfig | |
{ | |
font = "xft:Bitstream Vera Sans Mono:pixelsize=16" | |
, promptBorderWidth = 0 | |
, fgHLight = "grey80" | |
, bgHLight = "maroon4" | |
, fgColor = "grey80" | |
, autoComplete = Just 500000 | |
, searchPredicate = L.isInfixOf | |
, bgColor = "grey11" | |
, position = Top | |
} | |
--{{{ Testing | |
toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.view | |
{-toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.greedyView-} | |
--}}} | |
-- | |
scratchpads = [ NS "zim" "zim" (className =? "Zim") nonFloating, | |
NS "emacs" "emacsclient -c" (className =? "Emacs") nonFloating, | |
NS "cemacs" "urxvt -name cemacs -e emacsclient -s /tmp/emacs1000/server -t" (appName =? "cemacs") nonFloating] | |
--{{{ Core | |
main = do | |
{-xmproc <- spawnPipe "xmobar --screen=0 ~/.xmobarrc.bigone"-} | |
-- FocusHook | |
xmonad $ withUrgencyHookC NoUrgencyHook urgentConfig $ defaultConfig { | |
terminal = myTerminal, | |
focusFollowsMouse = myFocusFollowsMouse, | |
borderWidth = myBorderWidth, | |
modMask = myModMask, | |
workspaces = myWorkspaces, | |
normalBorderColor = myNormalBorderColor, | |
focusedBorderColor = myFocusedBorderColor, | |
keys = myKeys, | |
layoutHook = myLayout, | |
manageHook = namedScratchpadManageHook scratchpads <+> transience' <+> myManageHook <+> manageDocks, | |
{-manageHook = insertPosition Below Newer <+> myManageHook,-} | |
handleEventHook = myEventHook <+> minimizeEventHook, | |
logHook = fadeWindowsLogHook myFadeHook <+> G.historyHook <+> myLogHook, | |
{-logHook = fadeInactiveCurrentWSLogHook myFadeHook <+> myLogHook xmproc,-} | |
{-logHook = myLogHook xmproc,-} | |
startupHook = myStartupHook | |
} | |
--}}} | |
-- | |
--{{{ | |
urgentConfig = UrgencyConfig { suppressWhen = XMonad.Hooks.UrgencyHook.Never, remindWhen = Repeatedly 3 10 } | |
--}}} | |
--{{{ Variables | |
myTerminal = "urxvt" | |
myFocusFollowsMouse :: Bool | |
myFocusFollowsMouse = False | |
myBorderWidth = 0 | |
myModMask = mod4Mask | |
myNormalBorderColor = "grey23" | |
myFocusedBorderColor = "grey56" | |
--}}} | |
-- Build a list of windowsets with current swapped in turn with each | |
-- "most recent" workspace as given by nonEmptyTags | |
nonEmptyRecents :: (Eq s, Eq i) => W.StackSet i l a s sd -> [W.StackSet i l a s sd] | |
{-nonEmptyRecents ws = map (W.view `flip` ws) (map (skipTags `flip` ["NSP"]) (rotUp $ nonEmptyTags ws))-} | |
nonEmptyRecents ws = map (W.view `flip` ws) (rotUp $ nonEmptyTags ws) | |
-- Given a windowset grab a list of the workspace tags, in the default order: | |
-- current, visibles in screen order, hiddens from most to least recently accessed. | |
nonEmptyTags :: W.StackSet i l a s sd -> [i] | |
nonEmptyTags ws = [ tag | W.Workspace tag _ (Just _) <- W.workspaces ws] | |
-- rotUp and rotDown are actually exported by Actions.CycleWindows, | |
-- but written in an unsafe form using head tail init last :(( | |
-- Shall have to send patch to fix that. | |
rotUp :: [a] -> [a] | |
rotUp l = drop 1 w ++ take 1 w | |
where w = init l | |
gsconfig1 = defaultGSConfig { gs_cellheight = 50, gs_cellwidth = 500, gs_navigate = myNavigation } | |
myNavigation :: TwoD a (Maybe a) | |
myNavigation = makeXEventhandler $ shadowWithKeymap navKeyMap navDefaultHandler | |
where navKeyMap = M.fromList [ | |
((0,xK_semicolon), cancel) | |
,((0,xK_KP_7), cancel) | |
,((0,xK_Escape), cancel) | |
,((0,xK_F13), cancel) | |
,((0,xK_q), cancel) | |
,((0,xK_asciitilde), cancel) | |
,((0,xK_Return), select) | |
,((0,xK_KP_9), select) | |
,((0,xK_e), select) | |
,((0,xK_slash) , substringSearch myNavigation) | |
,((0,xK_KP_Divide) , substringSearch myNavigation) | |
,((0,xK_Left) , move (-1,0) >> myNavigation) | |
,((0,xK_a) , move (-1,0) >> myNavigation) | |
,((0,xK_KP_4) , move (-1,0) >> myNavigation) | |
,((0,xK_h) , move (-1,0) >> myNavigation) | |
,((0,xK_Right) , move (1,0) >> myNavigation) | |
,((0,xK_d) , move (1,0) >> myNavigation) | |
,((0,xK_KP_6) , move (1,0) >> myNavigation) | |
,((0,xK_l) , move (1,0) >> myNavigation) | |
,((0,xK_Down) , move (0,1) >> myNavigation) | |
,((0,xK_s) , move (0,1) >> myNavigation) | |
,((0,xK_KP_2) , move (0,1) >> myNavigation) | |
,((0,xK_j) , move (0,1) >> myNavigation) | |
,((0,xK_Up) , move (0,-1) >> myNavigation) | |
,((0,xK_w) , move (0,-1) >> myNavigation) | |
,((0,xK_KP_8) , move (0,-1) >> myNavigation) | |
,((0,xK_y) , move (-1,-1) >> myNavigation) | |
,((0,xK_i) , move (1,-1) >> myNavigation) | |
,((0,xK_n) , move (-1,1) >> myNavigation) | |
,((0,xK_m) , move (1,-1) >> myNavigation) | |
,((0,xK_space) , setPos (0,0) >> myNavigation) | |
] | |
-- The navigation handler ignores unknown key symbols | |
navDefaultHandler = const myNavigation | |
--{{{ Keybindings | |
--myKeys conf = mkKeymap conf $ | |
myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $ | |
[ ((modm, xK_d ), kill1) | |
, ((mod1Mask .|. shiftMask, xK_d ), kill1) | |
, ((modm, xK_r), withFocused toggleBorder) | |
, ((modm, xK_Right), windowGo R False) | |
, ((modm, xK_Left ), windowGo L False) | |
, ((modm, xK_Up ), windowGo U False) | |
, ((modm, xK_Down ), windowGo D False) | |
, ((mod1Mask, xK_F13), toggleWS' ["NSP"] ) | |
, ((modm, xK_space), toggleWS' ["NSP"] ) | |
, ((modm .|. shiftMask, xK_w), windows W.focusUp ) | |
, ((0, xK_F16),windows W.focusDown) | |
, ((shiftMask, xK_F16),windows W.focusUp) | |
{-, ((modm , xK_F13), nextMatch History (return True))-} | |
, ((modm , xK_F13), nextMatchWithThis History currentWs) | |
, ((modm, xK_KP_Subtract), windows W.focusDown ) | |
, ((modm, xK_s), swapPrevScreen ) | |
, ((modm, xK_p), nextScreen) | |
{-, ((modm .|. controlMask, xK_s), doTo Next EmptyWS getSortByIndex $ \ws -> windows (W.shift ws) >> swapPrevScreen >> windows(toggleOnScreen 1 ws))-} | |
, ((modm .|. controlMask, xK_s), doTo Next EmptyWS getSortByIndex $ \ws -> windows (W.shift ws)) | |
, ((modm .|. mod1Mask, xK_s), doTo Next EmptyWS getSortByIndex $ \ws -> windows (W.shift ws) >> windows(toggleOnScreen 1 ws)) | |
, ((modm .|. shiftMask, xK_s), doTo Next EmptyWS getSortByIndex $ \ws -> windows (W.shift ws) >> windows (W.greedyView ws)) | |
, ((mod1Mask .|. shiftMask, xK_a), swapPrevScreen ) | |
, ((modm, xK_a), swapPrevScreen >> nextScreen) | |
, ((modm , xK_BackSpace), focusUrgent) | |
, ((modm, xK_semicolon), sendMessage NextLayout) | |
, ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) | |
, ((modm .|. controlMask , xK_plus ), sendMessage MagnifyMore) | |
, ((modm .|. controlMask , xK_minus), sendMessage MagnifyLess) | |
, ((modm .|. controlMask, xK_t), themePrompt myXPConfig) | |
{-, ((modm, xK_n), runOrRaise "zim" (className =? "zim"))-} | |
, ((modm, xK_n), namedScratchpadAction scratchpads "zim") | |
, ((shiftMask, xK_Return), namedScratchpadAction scratchpads "emacs") | |
, ((modm .|. shiftMask, xK_Return), namedScratchpadAction scratchpads "cemacs") | |
{-, ((controlMask, xK_Tab), cycleWindowSets nonEmptyRecents [xK_Alt_L] xK_Tab xK_Tab)-} | |
, ((modm, xK_Next), cycleWindowSets nonEmptyRecents [xK_Super_L] xK_Next xK_Prior) | |
, ((modm, xK_Prior), cycleRecentWS [xK_Super_L] xK_Next xK_Prior) | |
, ((modm , xK_h), nextMatchWithThis Forward className) | |
, ((modm , xK_b), nextMatchWithThis Backward className) | |
, ((modm, xK_q), nextScreen) | |
, ((0, xK_F1), nextScreen) | |
{-, ((controlMask, xK_space), nextScreen)-} | |
, ((modm, xK_j), BW.focusUp) | |
, ((modm, xK_k), BW.focusDown) | |
{-, ((mod1Mask, xK_Tab), windows W.focusDown)-} | |
, ((mod1Mask, xK_Tab), BW.focusDown) | |
, ((mod1Mask .|. shiftMask, xK_Tab), BW.focusUp) | |
, ((mod1Mask, xK_asciitilde), cycleWindowSets nonEmptyRecents [xK_Alt_L] xK_asciitilde xK_asciitilde) | |
{-, ((modm, xK_e), sendMessage $ T.Toggle FULL)-} | |
, ((mod1Mask, xK_Escape), sendMessage $ T.Toggle FULL) | |
, ((modm, xK_i), bringRestoredWindow) | |
{-, ((modm, xK_o ), windowMenu)-} | |
, ((modm, xK_m ), withFocused minimizeWindow) | |
, ((modm .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin) | |
, ((modm .|. controlMask, xK_x), xmonadPrompt myXPConfig) | |
, ((modm .|. controlMask, xK_r), runOrRaisePrompt myXPConfig) | |
, ((modm , xK_z), windowPromptGoto myXPConfig) | |
, ((modm , xK_x), windowPromptBring myXPConfig) | |
, ((modm , xK_c), windowPromptBringCopy myXPConfig) | |
, ((modm, xK_KP_Multiply), sendMessage ToggleStruts) | |
, ((modm .|. shiftMask, xK_j ), BW.focusMaster ) | |
{-, ((modm .|. shiftMask, xK_m ), tagToEmptyWorkspace)-} | |
, ((modm, xK_KP_Add ), nextScreen ) | |
{-, ((modm, xK_b ), runOrCopy "firefox" (className =? "Firefox")) -- @@ run or copy firefox-} | |
, ((modm , xK_g ), sendMessage Mag.Toggle) | |
, ((modm .|. shiftMask, xK_t ), sinkAll) | |
, ((modm, xK_Return), windows W.swapMaster) | |
, ((modm .|. shiftMask, xK_q), spawn "xmonad --recompile; strip ~/.xmonad/xmonad-x86_64-linux; xmonad --restart; ICON=xmonad notify-send XMonad Restarted") | |
, ((modm, xK_KP_Enter), goToSelected gsconfig1) | |
, ((modm .|. shiftMask, xK_KP_Enter), bringSelected gsconfig1) | |
, ((modm, xK_quoteright), goToSelected gsconfig1) | |
, ((mod1Mask .|. shiftMask, xK_w), goToSelected gsconfig1) | |
, ((modm .|. shiftMask, xK_quoteright), bringSelected gsconfig1) | |
, ((modm, xK_slash), spawnSelected gsconfig1 ["firefox","urxvt","gedit", "showpass", "google-chrome-private", "google-chrome-tor", "chromium","xterm","opera-next","pavucontrol","oskype","oskype percona.raghavendrap","calibre","oskype twitterelf" ]) | |
, ((mod1Mask .|. shiftMask, xK_q), spawnSelected gsconfig1 ["firefox","urxvt","gedit", "showpass", "google-chrome-private", "google-chrome-tor", "chromium","xterm","opera-next","pavucontrol","oskype","oskype percona.raghavendrap","calibre","oskype twitterelf" ]) | |
, ((modm, xK_t ), withFocused $ windows . W.sink) | |
, ((controlMask , xK_comma ), sendMessage (IncMasterN 1)) | |
, ((controlMask , xK_period), sendMessage (IncMasterN (-1))) | |
, ((modm .|. shiftMask .|. controlMask, xK_q ), io (exitWith ExitSuccess)) | |
] | |
++ | |
[((m .|. modm, k), windows(f i)) | |
| (i, k) <- zip (XMonad.workspaces conf) numKeys2 | |
, (f, m) <- [ (toggleOnScreen 0, 0), (toggleOnScreen 1, mod1Mask), (W.greedyView, controlMask .|. shiftMask) ]] | |
++ | |
[((m .|. modm, k), f i) | |
| (i, k) <- zip (XMonad.workspaces conf) numKeys | |
, (f, m) <- [(toggleOrViewNoSP, 0), (windows . W.shift, shiftMask), (windows . copy, mod1Mask)]] | |
++ | |
[((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f)) | |
| (key, sc) <- zip [xK_o,xK_p] [0..] | |
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] | |
numKeys = [ xK_KP_End, xK_KP_Down, xK_KP_Page_Down -- 1, 2, 3 | |
, xK_KP_Left, xK_KP_Begin, xK_KP_Right -- 4, 5, 6 | |
, xK_KP_Home, xK_KP_Up, xK_KP_Page_Up -- 7, 8, 9 | |
, xK_KP_Insert] -- 0 | |
numKeys2 = [xK_1 ..] | |
--}}} | |
--{{{ Layout | |
myLayout = onWorkspace "4:video" brLayout $ onWorkspace "8:games" myFull $ defLayout | |
where | |
{-defLayout = avoidStruts $ T.mkToggle (T.single FULL) $ minimize $ boringWindows ( tiled ||| Mirror tiled ||| myFull)-} | |
defLayout = minimize $ boringWindows $ avoidStruts $ T.mkToggle (T.single FULL) ( tiled ||| Mirror tiled ||| myFull) | |
{-defLayout = minimize $ boringWindows $ avoidStruts $ T.mkToggle (T.single FULL) (hintedTile HT.Tall ||| hintedTile HT.Wide ||| myFull)-} | |
{-tiled = mgFy $ smartBorders tall-} | |
tiled = smartBorders tall | |
{-tall = ResizableTall 1 (3/100) (1/2) []-} | |
{-hintedTile = HintedTile nmaster delta ratio TopLeft-} | |
{-nmaster = 1-} | |
{-ratio = 1/2-} | |
{-delta = 3/100-} | |
tall = XMonad.Tall 1 (3/100) (1/2) | |
brLayout = avoidStruts $ T.mkToggle (T.single FULL) (Mirror tiled ||| tiled ||| myFull) | |
mgFy = Mag.magnifiercz 1.05 | |
{-myFull = tabbed shrinkText myTabConfig-} | |
myFull = tabbed shrinkText myTabConfig | |
{-myFull = Simplest-} | |
{-myFull = StackTile 1 (3/100) (1/10)-} | |
--}}} | |
--{{{ Workspaces | |
myWorkspaces :: [WorkspaceId] | |
myWorkspaces = ["1:norm","2:term","3:browser","4:video","5:pdf","6:note","7:thunar","8:games","9:misc"] | |
myManageHook = composeAll . concat $ | |
[ | |
[ className =? "MPlayer" --> doShift "4:video" ] | |
, [ className =? "mplayer2" --> doShift "4:video" ] | |
, [ className =? s --> doSink | s <- sinkit ] | |
, [ className =? "vlc" --> doShift "4:video" ] | |
, [ appName =? "URxvt" --> doShift "1:norm" ] | |
, [ appName =? "dactyl" --> doCenterFloat ] | |
, [ isFullscreen --> doFullFloat ] | |
, [ className =? "Wine" --> doShift "8:games" ] | |
, [ className =? "xbmc.bin" --> doShift "8:games" ] | |
, [ className =? "VirtualBox" --> doShift "8:games" ] | |
, [ className =? "Calibre-gui" --> doShift "6:note" ] | |
, [ className =? "libreoffice-calc" --> doShift "6:note" ] | |
, [ className =? "Xfce4-notifyd" --> doIgnore ] | |
, [ resource =? c --> doIgnore | c <- myIgnores ] | |
, [ className =? b --> doShift "3:browser" | b <- myBrowsers ] | |
, [ className =? "l" --> doShift "7:thunar" | l <- myThings ] | |
, [ className =? "Skype" --> doShift "9:misc" ] | |
, [ className =? "Rednotebook" --> doShift "6:note" ] | |
, [ className =? d <||> isDialog --> doCenterFloat | d <- myCenterFloats ]] | |
{-, [ className =? e --> doShift "5:pdf" | e <- myPDF ] -} | |
where | |
myCenterFloats = ["Xmessage","feh","Gxmessage","MuPDF"] | |
sinkit = ["dosbox" ] | |
myBrowsers = ["Firefox", "Aurora", "Navigator", "Opera", "OperaNext", "Google-chrome"] | |
myPDF = ["Evince","Zathura","Apvlv", "Okular"] | |
myIgnores = ["desktop_window","desktop"] | |
myThings = ["Thunar","Skype"] | |
--}}} | |
doSink :: ManageHook | |
doSink = ask >>= \w -> liftX (reveal w) >> doF (W.sink w) | |
--{{{ Events | |
myEventHook = fullscreenEventHook | |
--}}} | |
--{{{ Startup | |
myStartupHook = setWMName "xmonad" <+> | |
spawn "turx" | |
<+> spawn "ssh-add -l | grep -q id_rsa || ssh-add" | |
--}}} | |
--{{{ LogHook | |
myLogHook :: X() | |
myLogHook = do | |
copies <- wsContainingCopies | |
let check ws | ws `elem` copies = pad . xmobarColor "red" "black" $ ws | |
| otherwise = pad $ noScratchPad ws | |
(dynamicLogString $ customPP { ppHidden = check }) >>= xmonadPropLog | |
where | |
noScratchPad ws = if ws == "NSP" then "" else pad ws | |
myFadeHook = composeAll [ isUnfocusedOnCurrentWS --> opacity 0.88 | |
, className =? "mplayer2" --> opaque | |
, className =? "Plugin-container" --> opaque | |
] | |
customPP :: PP | |
customPP = defaultPP { | |
ppHidden = xmobarColor "grey58" "" . noScratchPad | |
, ppOrder = \(ws:l:t:_) -> [l,ws,t] | |
, ppVisible = xmobarColor "skyblue" "" . wrap "/" "/" | |
, ppCurrent = xmobarColor "skyblue" "" . wrap "#" "#" | |
, ppUrgent = xmobarColor "green" "" . wrap "*" "*" | |
, ppWsSep = " " | |
, ppLayout = xmobarColor "SlateGray2" "" . wrap "[" "]" | |
, ppTitle = xmobarColor "SlateGray2" "" . shorten 65 | |
, ppSep = "<fc=#0033FF> % </fc>" | |
, ppSort = getSortByXineramaRule | |
} | |
where | |
noScratchPad ws = if ws == "NSP" then "" else pad ws | |
bringRestored :: Window -> X () | |
bringRestored w = do | |
broadcastMessage (RestoreMinimizedWin w) | |
windows (bringWindow w) | |
bringRestoredWindow = do | |
wm <- windowMap | |
w <- menuArgs "dmenu" ["-p", ":", "-i", "-l","40", "-nb", "grey11", "-nf", "grey80", "-sb", "maroon4", "-fn", "xft:Liberation:pixelsize=14"] (M.keys wm) | |
whenJust (M.lookup w wm) bringRestored | |
--}}} |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment