From dpx at binaryapparatus.com Sat Jan 4 09:38:48 2020 From: dpx at binaryapparatus.com (Dusan Popovic) Date: Sat, 4 Jan 2020 10:38:48 +0100 Subject: [xmonad] Is there a better way to write new layout? (Also modified Tall layout inside) Message-ID: <20200104093848.GA833817@maglev.localdomain> Hi, With being near impossible to get any non 16:9 monitor, and using big monitor (27" or bigger), any single terminal/editor takes entire screen when using Tall layout. This makes all the text aligned at the left edge of the monitor, which forces me to either sit facing the left half of the monitor or stretch my neck 90+% of time. I decided to modify Tall layout, so that with single window open it doesn't take all the space, while with more than one window open it behaves exactly as Tall already does. I am really beginner in haskell but I can do basic stuff, so I chopped built in Tall layout, modified it a bit, added to xmonad.hs. While it works well I am convinced there must be more elegant way to do the same, so I am curious how to do it better. Steps I took to make it work: 1. Chop LANGUAGE directive from xmonad-git/src/XMonad/Layout.hs and add to my xmonad.hs at the top. I would love to avoid having FlexibleInstances in my xmonad.hs. {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances, DeriveDataTypeable #-} 2. Chop and modify Tall layout, add it to xmonad.sh, most important part being 'tile54 f (Rectangle sx sy sw sh) nmaster 1' function that matches when there is only one window. import Control.Arrow ((***), second) import Control.Monad import Graphics.X11 (Rectangle(..)) data Tall54 a = Tall54 { tallNMaster :: !Int -- ^ The default number of windows in the master pane (default: 1) , tallRatioIncrement :: !Rational -- ^ Percent of screen to increment by when resizing panes (default: 3/100) , tallRatio :: !Rational -- ^ Default proportion of screen occupied by master pane (default: 1/2) } deriving (Show, Read) instance LayoutClass Tall54 a where pureLayout (Tall54 nmaster _ frac) r s = zip ws rs where ws = W.integrate s rs = tile54 frac r nmaster (length ws) pureMessage (Tall54 nmaster delta frac) m = msum [fmap resize (fromMessage m) ,fmap incmastern (fromMessage m)] where resize Shrink = Tall54 nmaster delta (max 0 $ frac-delta) resize Expand = Tall54 nmaster delta (min 1 $ frac+delta) incmastern (IncMasterN d) = Tall54 (max 0 (nmaster+d)) delta frac description _ = "Tall54" tile54 :: Rational -- ^ @frac@, what proportion of the screen to devote to the master area -> Rectangle -- ^ @r@, the rectangle representing the screen -> Int -- ^ @nmaster@, the number of windows in the master pane -> Int -- ^ @n@, the total number of windows to tile -> [Rectangle] tile54 f (Rectangle sx sy sw sh) nmaster 1 = [Rectangle sx1 sy sw1 sh] where sx1 = sx + sm1 sm1 = fromIntegral (sw - sw1) `div` 2 sw1 = 5 * fromIntegral (sh `div` 4) tile54 f r nmaster n = if n <= nmaster || nmaster == 0 then splitVertically n r else splitVertically nmaster r1 ++ splitVertically (n-nmaster) r2 -- two columns where (r1,r2) = splitHorizontallyBy f r 3. Add new layout in the list, keeping standard Tall as second one. In rare cases when I want single window taking entire screen I can switch to Tall. As a result, when I open single terminal or editor window it is centered, simulating old 5:4 monitors. More than one window and it is standard Tall layout. I have attached my xmonad.hs if somebody wants to try. So finally questions: 1. Anybody needs this apart from me? How do you cope with 'teaminal/editor being too far to the left'? 2. Is there a better way to write this layout (in xmonad.hs) without butchering parts of code from Layout.hs? Since I am learning haskell I believe any pointers would be very useful. Cheers, Dusan -------------- next part -------------- {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances, DeriveDataTypeable #-} import System.IO import System.Exit import XMonad import XMonad.Hooks.DynamicLog import XMonad.Hooks.ManageDocks import XMonad.Hooks.ManageHelpers import XMonad.Hooks.SetWMName import XMonad.Layout.Fullscreen import XMonad.Layout.NoBorders import XMonad.Layout.Spiral import XMonad.Layout.Tabbed import XMonad.Layout.ThreeColumns import XMonad.Layout.SimpleFloat import XMonad.Util.Run(spawnPipe) import XMonad.Hooks.UrgencyHook import qualified XMonad.StackSet as W import qualified Data.Map as M import Data.List(foldl') import XMonad.Hooks.EwmhDesktops as E import XMonad.Actions.WindowBringer import XMonad.Util.WorkspaceCompare import XMonad.Actions.PhysicalScreens import XMonad.Util.SpawnOnce (spawnOnce) import Control.Arrow ((***), second) import Control.Monad import Graphics.X11 (Rectangle(..)) data Tall54 a = Tall54 { tallNMaster :: !Int -- ^ The default number of windows in the master pane (default: 1) , tallRatioIncrement :: !Rational -- ^ Percent of screen to increment by when resizing panes (default: 3/100) , tallRatio :: !Rational -- ^ Default proportion of screen occupied by master pane (default: 1/2) } deriving (Show, Read) instance LayoutClass Tall54 a where pureLayout (Tall54 nmaster _ frac) r s = zip ws rs where ws = W.integrate s rs = tile54 frac r nmaster (length ws) pureMessage (Tall54 nmaster delta frac) m = msum [fmap resize (fromMessage m) ,fmap incmastern (fromMessage m)] where resize Shrink = Tall54 nmaster delta (max 0 $ frac-delta) resize Expand = Tall54 nmaster delta (min 1 $ frac+delta) incmastern (IncMasterN d) = Tall54 (max 0 (nmaster+d)) delta frac description _ = "Tall54" tile54 :: Rational -- ^ @frac@, what proportion of the screen to devote to the master area -> Rectangle -- ^ @r@, the rectangle representing the screen -> Int -- ^ @nmaster@, the number of windows in the master pane -> Int -- ^ @n@, the total number of windows to tile -> [Rectangle] tile54 f (Rectangle sx sy sw sh) nmaster 1 = [Rectangle sx1 sy sw1 sh] where sx1 = sx + sm1 sm1 = fromIntegral (sw - sw1) `div` 2 sw1 = 5 * fromIntegral (sh `div` 4) tile54 f r nmaster n = if n <= nmaster || nmaster == 0 then splitVertically n r else splitVertically nmaster r1 ++ splitVertically (n-nmaster) r2 -- two columns where (r1,r2) = splitHorizontallyBy f r modm = mod4Mask myTerminal = "alacritty" superMask = mod4Mask .|. controlMask .|. mod1Mask myWorkspaces = map show [1..9] myManageHook = composeAll [ resource =? "desktop_window" --> doIgnore , className =? "Galculator" --> doFloat , resource =? "gpicview" --> doFloat , className =? "MPlayer" --> doFloat , className =? "stalonetray" --> doIgnore , className =? "conky" --> doIgnore , className =? "xclock" --> doIgnore , className =? "Dunst" --> doIgnore , className =? "Cairo-clock" --> doIgnore , className =? "Deezer" --> doCenterFloat , className =? "Zenity" --> doCenterFloat , className =? "Hamster" --> doCenterFloat , className =? "Xdialog" --> doCenterFloat , className =? "Pinentry-gtk-2" --> doCenterFloat , className =? "Chromium" --> doShift "8:web" , className =? "SDL_App" --> doCenterFloat , isFullscreen --> (doF W.focusDown <+> doFullFloat) ] main = do xmobarpipe <- spawnPipe "xmobar -x 1 ~/.xmonad/xmobarrc.hs" xmonad $ withUrgencyHook NoUrgencyHook $ ewmh defaults { logHook = dynamicLogWithPP $ xmobarPP { ppOutput = hPutStrLn xmobarpipe , ppTitle = shorten 60 . wrap "" "" , ppCurrent = xmobarColor "#a89984" "#665c54" . wrap " " " " . xmobarPPName , ppVisible = xmobarColor "#a89984" "#3c3836" . wrap " " " " . xmobarPPName , ppHidden = wrap " " " " . xmobarPPName , ppUrgent = xmobarColor "#cc241d" "" . wrap " " " " . xmobarPPName , ppSep = "" , ppWsSep = "" , ppLayout = wrap " " " " . xmobarPPLayout , ppSort = getSortByXineramaPhysicalRule horizontalScreenOrderer , ppOrder = reverse } } xmobarPPLayout x = case x of "Tall54" -> "[=]" "Tall" -> "[]=" "Mirror Tall" -> "TTT" "ThreeCol" -> "|||" "Tabbed Bottom Simplest" -> "___" "Full" -> "[F]" "Spiral" -> "[@]" "Simple Float" -> "<->" _ -> pad x xmobarPPName x = x --xmobarPPName x = tail $ tail x myStartup :: X () myStartup = spawnOnce "xdotool key super+q super+6 super+w super+1" defaults = def { terminal = myTerminal , modMask = modm , workspaces = myWorkspaces , startupHook = startupHook def <+> setWMName "LG3D" <+> docksStartupHook <+> myStartup , focusFollowsMouse = True , normalBorderColor = "#3c3836" , focusedBorderColor = "#ff0000" , borderWidth = 2 , layoutHook=myLayout , manageHook=manageHook def <+> manageDocks <+> myManageHook , handleEventHook = handleEventHook def <+> E.fullscreenEventHook <+> docksEventHook -- <+> floatClickFocusHandler , keys = myKeys , mouseBindings = myMouseBindings } myLayout = smartBorders $ avoidStruts ( Tall54 1 (3/100) (1/2) ||| Tall 1 (3/100) (1/2) ||| Mirror (Tall 1 (3/100) (1/2)) ||| Full ||| simpleFloat ||| ThreeColMid 1 (3/100) (1/2) ||| tabbedBottomAlways shrinkText tabConfig ||| spiral (6/7)) ||| noBorders (fullscreenFull Full) tabConfig = def { activeBorderColor = "#3c3836", activeTextColor = "#ebdbb2", activeColor = "#3c3836", inactiveBorderColor = "#1d2021", inactiveTextColor = "#ebdbb2", inactiveColor = "#1d2021", fontName = "xft:Source Code Pro for Powerline:style=Semibold:pixelsize=10.5:antialias=true:hintstyle=hintfull:hinting=true" } ------------------------------------------------------------------------ myKeys conf@ XConfig {XMonad.modMask = modm} = M.fromList $ [ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf) , ((modm, xK_g ), spawn "dmenu_run") , ((modm .|. shiftMask, xK_c ), kill) , ((modm, xK_space ), sendMessage NextLayout) , ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) , ((modm, xK_s ), refresh) , ((modm, xK_Tab ), windows W.focusDown) , ((modm .|. shiftMask, xK_Tab ), windows W.focusUp ) , ((modm, xK_m ), windows W.focusMaster ) , ((modm, xK_Return), windows W.swapMaster) , ((modm .|. shiftMask, xK_o ), windows W.swapDown ) , ((modm .|. shiftMask, xK_n ), windows W.swapUp ) , ((modm, xK_n ), sendMessage Shrink) , ((modm, xK_o ), sendMessage Expand) , ((modm, xK_t ), withFocused $ windows . W.sink) , ((modm, xK_comma ), sendMessage (IncMasterN 1)) , ((modm, xK_period), sendMessage (IncMasterN (-1))) , ((modm, xK_b ), sendMessage ToggleStruts) -- Hide / show xmobar , ((modm .|. shiftMask .|. controlMask, xK_q ), io exitSuccess) -- Quit xmonad , ((modm .|. controlMask, xK_q ), spawn "notify-send 'Kompajliram'; xmonad --recompile; xmonad --restart") -- Restart xmonad , ((modm .|. shiftMask, xK_minus), spawn "import -window root ~/desktop/$(date +%F_%H%M%S_%N).png") -- Screenshot whole screen , ((modm .|. shiftMask, xK_backslash), spawn "import -window \"$(xdotool getwindowfocus -f)\" ~/desktop/$(date +%F_%H%M%S_%N).png") -- Screenshot focused window , ((modm .|. shiftMask, xK_g ), gotoMenuArgs ["-l","30"]) -- GotoMenu , ((modm .|. shiftMask, xK_i ), spawn "firefox") , ((modm .|. shiftMask, xK_r ), spawn "alacritty -e vifm") , ((modm .|. shiftMask, xK_t ), spawn "~/bin/st/st -e todo") , ((modm .|. shiftMask, xK_e ), spawn "gvim") , ((superMask, xK_f ), spawn "mixer vol -5") , ((shiftMask, xK_F7 ), spawn "mixer vol -5") , ((superMask, xK_e ), spawn "mixer vol +5") , ((shiftMask, xK_F8 ), spawn "mixer vol +5") , ((superMask, xK_a ), spawn "dpass") , ((shiftMask, xK_F12 ), spawn "dpass") , ((superMask, xK_b ), spawn "mpc toggle") , ((shiftMask, xK_F9 ), spawn "mpc toggle") , ((superMask, xK_c ), spawn "mpc stop") , ((shiftMask, xK_F10 ), spawn "mpc stop") , ((superMask, xK_d ), spawn "mpc play") , ((shiftMask, xK_F11 ), spawn "mpc play") , ((shiftMask .|. superMask, xK_d), spawn "~/bin/mpcplay") , ((shiftMask .|. modm, xK_F11 ), spawn "~/bin/mpcplay") , ((shiftMask .|. superMask, xK_c), spawn "~/bin/helpers/toggledeezer") ] ++ -- mod-[1..9], Switch to workspace N, mod-shift-[1..9], Move client to workspace N [((m .|. modm, k), windows $ f i) | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9] , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] ++ -- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3, mod-shift-{w,e,r}, Move client to screen 1, 2, or 3 [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f)) | (key, sc) <- zip [xK_q, xK_w, xK_f] [1,0..] -- bilo [0..] , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] ------------------------------------------------------------------------ myMouseBindings XConfig {XMonad.modMask = modm} = M.fromList -- mod-button1, Set the window to floating mode and move by dragging [ ((modm, button1), \w -> focus w >> mouseMoveWindow w >> windows W.shiftMaster) -- mod-button2, Raise the window to the top of the stack , ((modm, button2), \w -> focus w >> windows W.shiftMaster) -- mod-button3, Set the window to floating mode and resize by dragging , ((modm .|. shiftMask, button1), \w -> focus w >> mouseResizeWindow w >> windows W.shiftMaster) -- you may also bind events to the mouse scroll wheel (button4 and button5) ] -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: not available URL: From allbery.b at gmail.com Mon Jan 6 17:30:03 2020 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 6 Jan 2020 12:30:03 -0500 Subject: [xmonad] Is there a better way to write new layout? (Also modified Tall layout inside) In-Reply-To: <20200104093848.GA833817@maglev.localdomain> References: <20200104093848.GA833817@maglev.localdomain> Message-ID: In general, we do things like this with layout modifiers so they can be applied to more than one layout. In this case, you might get some ideas from X.L.Magnifier or X.L.Maximize: the former enlarges the focused window in a layout, the latter lets you pop out a window to "almost fullscreen" (it has a gap which IIRC can be configured in recent versions). There's also X.L.IfMax which lets you conditionalize on how many windows a layout has, so you almost have the pieces needed to build what you want (X.L.Magnifier with X.L.IfMax is not quite it because there's no gap, and X.L.Maximize needs to be triggered by a keypress). On Sat, Jan 4, 2020 at 4:41 AM Dusan Popovic wrote: > Hi, > > With being near impossible to get any non 16:9 monitor, and using big > monitor (27" or bigger), any single terminal/editor takes entire screen > when using Tall layout. This makes all the text aligned at the left edge > of the monitor, which forces me to either sit facing the left half of > the monitor or stretch my neck 90+% of time. I decided to modify Tall > layout, so that with single window open it doesn't take all the space, > while with more than one window open it behaves exactly as Tall already > does. > > I am really beginner in haskell but I can do basic stuff, so I chopped > built in Tall layout, modified it a bit, added to xmonad.hs. While it > works well I am convinced there must be more elegant way to do the same, > so I am curious how to do it better. > > Steps I took to make it work: > > 1. Chop LANGUAGE directive from xmonad-git/src/XMonad/Layout.hs and add > to my xmonad.hs at the top. I would love to avoid having > FlexibleInstances in my xmonad.hs. > > {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, > PatternGuards, TypeSynonymInstances, DeriveDataTypeable #-} > > 2. Chop and modify Tall layout, add it to xmonad.sh, most important part > being 'tile54 f (Rectangle sx sy sw sh) nmaster 1' function that matches > when there is only one window. > > import Control.Arrow ((***), second) > import Control.Monad > import Graphics.X11 (Rectangle(..)) > > data Tall54 a = Tall54 { tallNMaster :: !Int -- ^ > The default number of windows in the master pane (default: 1) > , tallRatioIncrement :: !Rational -- ^ > Percent of screen to increment by when resizing panes (default: 3/100) > , tallRatio :: !Rational -- ^ > Default proportion of screen occupied by master pane (default: 1/2) > } > deriving (Show, Read) > > instance LayoutClass Tall54 a where > pureLayout (Tall54 nmaster _ frac) r s = zip ws rs > where ws = W.integrate s > rs = tile54 frac r nmaster (length ws) > > pureMessage (Tall54 nmaster delta frac) m = > msum [fmap resize (fromMessage m) > ,fmap incmastern (fromMessage m)] > > where resize Shrink = Tall54 nmaster delta (max > 0 $ frac-delta) > resize Expand = Tall54 nmaster delta (min > 1 $ frac+delta) > incmastern (IncMasterN d) = Tall54 (max 0 (nmaster+d)) > delta frac > > description _ = "Tall54" > > tile54 > :: Rational -- ^ @frac@, what proportion of the screen to > devote to the master area > -> Rectangle -- ^ @r@, the rectangle representing the screen > -> Int -- ^ @nmaster@, the number of windows in the > master pane > -> Int -- ^ @n@, the total number of windows to tile > -> [Rectangle] > tile54 f (Rectangle sx sy sw sh) nmaster 1 = [Rectangle sx1 sy sw1 > sh] > where sx1 = sx + sm1 > sm1 = fromIntegral (sw - sw1) `div` 2 > sw1 = 5 * fromIntegral (sh `div` 4) > tile54 f r nmaster n = if n <= nmaster || nmaster == 0 > then splitVertically n r > else splitVertically nmaster r1 ++ splitVertically (n-nmaster) > r2 -- two columns > where (r1,r2) = splitHorizontallyBy f r > > 3. Add new layout in the list, keeping standard Tall as second one. In > rare cases when I want single window taking entire screen I can switch > to Tall. > > As a result, when I open single terminal or editor window it is > centered, simulating old 5:4 monitors. More than one window and it is > standard Tall layout. I have attached my xmonad.hs if somebody wants to > try. > > So finally questions: > > 1. Anybody needs this apart from me? How do you cope with > 'teaminal/editor being too far to the left'? > > 2. Is there a better way to write this layout (in xmonad.hs) without > butchering parts of code from Layout.hs? Since I am learning haskell I > believe any pointers would be very useful. > > Cheers, > Dusan > _______________________________________________ > xmonad mailing list > xmonad at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From mestelan at gmail.com Fri Jan 10 09:20:07 2020 From: mestelan at gmail.com (Jean-Baptiste Mestelan) Date: Fri, 10 Jan 2020 10:20:07 +0100 Subject: [xmonad] Refresh display, adapting to monitor resolution Message-ID: Hello, Is there a way to have XMonad adapt the display to the resolution of the plugged monitor(s)? My problem is: at home, I have the laptop attached to one monitor. I suspend the session (systemctl hibernate), and resume it at work where I use a higher-resolution monitor. The display remains as it was set when starting the X session. The only way I have found to have the new monitor settings detected is to restart the X session (slim restart), which obviously kills user programs. So the question is: is there a command I can run to have the display adapt to the capabilities of the current monitor? Thanks for attention. -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexandre.n.medeiros at gmail.com Fri Jan 10 14:55:11 2020 From: alexandre.n.medeiros at gmail.com (alexandre medeiros) Date: Fri, 10 Jan 2020 11:55:11 -0300 Subject: [xmonad] Refresh display, adapting to monitor resolution In-Reply-To: References: Message-ID: Hi friend, I have a similar setup, at home I have a single monitor and use the laptop screen and the monitor and at work I have two monitors and don't use the laptop screen. I don't use XMonad itself to change the resolution, I use a program called autorandr , all you need to do is configure your resolution with xrandr and then save the profile with autorandr and it automatically detects the displays and the profile you saved for them. XMonad automatically adapts to this, changing the resolution and moving xmobar to the primary display. Hope this helps you! Best Regards, On Fri, Jan 10, 2020 at 6:20 AM Jean-Baptiste Mestelan wrote: > Hello, > > Is there a way to have XMonad adapt the display to the resolution of the > plugged monitor(s)? > My problem is: at home, I have the laptop attached to one monitor. I > suspend the session (systemctl hibernate), and resume it at work where I > use a higher-resolution monitor. The display remains as it was set when > starting the X session. The only way I have found to have the new monitor > settings detected is to restart the X session (slim restart), which > obviously kills user programs. So the question is: is there a command I can > run to have the display adapt to the capabilities of the current monitor? > > Thanks for attention. > _______________________________________________ > xmonad mailing list > xmonad at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad > -- Alexandre Medeiros Software Engineer @ Nubank BSc Computer Science - University of Campinas -------------- next part -------------- An HTML attachment was scrubbed... URL: From mestelan at gmail.com Sat Jan 11 12:03:52 2020 From: mestelan at gmail.com (Jean-Baptiste Mestelan) Date: Sat, 11 Jan 2020 13:03:52 +0100 Subject: [xmonad] Refresh display, adapting to monitor resolution In-Reply-To: References: Message-ID: Thank you very much, Alexandre, for your kind answer. Yes, I vaguely suspected that the answer might come from X tooling, rather than XMonad itself; but thanks for putting up with me. Looking at autorandr right now: it looks perfect for what I want. Best regards. On Fri, 10 Jan 2020 at 15:59, alexandre medeiros < alexandre.n.medeiros at gmail.com> wrote: > Hi friend, > > I have a similar setup, at home I have a single monitor and use the laptop > screen and the monitor and at work I have two monitors and don't use the > laptop screen. I don't use XMonad itself to change the resolution, I use a > program called autorandr , > all you need to do is configure your resolution with xrandr and then save > the profile with autorandr and it automatically detects the displays and > the profile you saved for them. XMonad automatically adapts to this, > changing the resolution and moving xmobar to the primary display. > > Hope this helps you! > > Best Regards, > > On Fri, Jan 10, 2020 at 6:20 AM Jean-Baptiste Mestelan > wrote: > >> Hello, >> >> Is there a way to have XMonad adapt the display to the resolution of the >> plugged monitor(s)? >> My problem is: at home, I have the laptop attached to one monitor. I >> suspend the session (systemctl hibernate), and resume it at work where I >> use a higher-resolution monitor. The display remains as it was set when >> starting the X session. The only way I have found to have the new monitor >> settings detected is to restart the X session (slim restart), which >> obviously kills user programs. So the question is: is there a command I can >> run to have the display adapt to the capabilities of the current monitor? >> >> Thanks for attention. >> _______________________________________________ >> xmonad mailing list >> xmonad at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad >> > > > -- > Alexandre Medeiros > Software Engineer @ Nubank > BSc Computer Science - University of Campinas > _______________________________________________ > xmonad mailing list > xmonad at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad > -------------- next part -------------- An HTML attachment was scrubbed... URL: From agarciafdz at gmail.com Sat Jan 25 21:10:44 2020 From: agarciafdz at gmail.com (Alejandro Garcia) Date: Sat, 25 Jan 2020 15:10:44 -0600 Subject: [xmonad] master window with fixed pixels layout. Message-ID: Hello first of all thank you for xmonad. the seconds I have saved every day by not having o drag and drop windows has given me more time to focus on what matters. get the job done and go home to play with my kids. I would like to know: Is there a window layout with the property that the width and height of the master window can be specified in pixels? my use case Is that I would like to record video casts. But it would be helpful for me if the window size of the master window stays fixed independently of the other windows open in the screen. I have checke FixedColumns. but on it the Width of the column is specified in a rare metric (characters?) plus the height is not fixed. Any recommendation ? Thanks in advance. -- Alejandro García F. (elviejo) Too brief? Here's why! http://emailcharter.org EOM – End Of Message. The whole message is in the subject don't need to open it. NNTR – No Need To Respond. Help cut down on all those “cool” and “thanks” emails. SINGLE SUBJECT. Send one email for one topic, this makes replies easy.. CLEAR CALL TO ACTION: Ask for some specific result very clearly. From allbery.b at gmail.com Sat Jan 25 21:13:12 2020 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 25 Jan 2020 16:13:12 -0500 Subject: [xmonad] master window with fixed pixels layout. In-Reply-To: References: Message-ID: xmonad does everything in terms of fractions of a screen size, because a workspace is not pinned to a particular monitor and monitors may have different resolutions. So it's not clear what a pixel-based size would do, especially if it were bigger than one of the monitors. On Sat, Jan 25, 2020 at 4:11 PM Alejandro Garcia wrote: > Hello first of all thank you for xmonad. > the seconds I have saved every day by not having o drag and drop windows > has given me more time to focus on what matters. > get the job done and go home to play with my kids. > > I would like to know: > Is there a window layout with the property that the width and height > of the master window can be specified in pixels? > > > my use case Is that I would like to record video casts. > But it would be helpful for me if the window size of the master window > stays fixed independently of the other windows open in the screen. > > I have checke FixedColumns. but on it the Width of the column is > specified in a rare metric (characters?) > plus the height is not fixed. > > Any recommendation ? > Thanks in advance. > > -- > Alejandro García F. (elviejo) > > Too brief? Here's why! http://emailcharter.org > > EOM – End Of Message. The whole message is in the subject don't need to > open it. > NNTR – No Need To Respond. Help cut down on all those “cool” and > “thanks” emails. > SINGLE SUBJECT. Send one email for one topic, this makes replies easy.. > CLEAR CALL TO ACTION: Ask for some specific result very clearly. > _______________________________________________ > xmonad mailing list > xmonad at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From e.a.gebhart at gmail.com Sun Jan 26 19:00:14 2020 From: e.a.gebhart at gmail.com (Eric Gebhart) Date: Sun, 26 Jan 2020 14:00:14 -0500 Subject: [xmonad] master window with fixed pixels layout. Message-ID: <-toftwv5m9co1zfkf6bj98anz-2u0ucd-xph93a-tbsgv2uc91ay-gij9rvsh1w1s3k2tc2gvc4qd-sj0ckl-sg7is22gpzxqvuwudc52b5ph-dgg1zsjhg70c7lcc-dzxsw3iibvfm1xsedz-xbuph.1580065214464@email.android.com> An HTML attachment was scrubbed... URL: