[xmonad] Re: patch: Unicode fix for XMonad.Hooks.EwmhDesktops
Don Stewart
dons at galois.com
Mon Feb 2 16:32:59 EST 2009
Have we decided whether to proceed with this?
utf8-string is a pretty ubiquitous package...
Spencer?
alexey.skladnoy:
> Thanks to Gwern Branwen I was able to make darcs patch.
>
> Note: XMonadContrib is not buildable without utf8-strings with this patch.
>
>
> Sat Jan 17 19:44:45 MSK 2009 Khudyakov Alexey <alexey.skladnoy at gmail.com>
> * Properly encode destop names before sending them to X server in XMonad.Hooks.EwmhDesktops
>
> New patches:
>
> [Properly encode destop names before sending them to X server in XMonad.Hooks.EwmhDesktops
> Khudyakov Alexey <alexey.skladnoy at gmail.com>**20090117164445] {
> hunk ./XMonad/Hooks/EwmhDesktops.hs 24
> ewmhDesktopsLayout
> ) where
>
> +import Codec.Binary.UTF8.String (encode)
> import Data.List
> import Data.Maybe
>
> hunk ./XMonad/Hooks/EwmhDesktops.hs 185
> r <- asks theRoot
> a <- getAtom "_NET_DESKTOP_NAMES"
> c <- getAtom "UTF8_STRING"
> - let names' = map (fromIntegral.fromEnum) $
> - concatMap (++['\0']) names
> + let names' = map fromIntegral $ concatMap ((++[0]) . encode) names
> io $ changeProperty8 dpy r a c propModeReplace names'
>
> setClientList :: [Window] -> X ()
> }
>
> Context:
>
> [Use spawnOn in my config
> Spencer Janssen <spencerjanssen at gmail.com>**20090117041026
> Ignore-this: 3f92e4bbe4f2874b86a6c7ad66a31bbb
> ]
> [Add XMonad.Actions.SpawnOn
> Spencer Janssen <spencerjanssen at gmail.com>**20090117040432
> Ignore-this: 63869d1ab11f2ed5aab1690763065800
> ]
> [Bump version to 0.8.1
> Spencer Janssen <spencerjanssen at gmail.com>**20090116223607
> Ignore-this: 1c201e87080e4404f51cadc108b228a1
> ]
> [Compile without optimizations on x86_64 and GHC 6.10
> Spencer Janssen <spencerjanssen at gmail.com>**20090108231650
> Ignore-this: a803235b8022793f648e8953d9f05e0c
> This is a workaround for http://xmonad.org/bugs/226
> ]
> [Update all uses of doubleFork/waitForProcess
> Spencer Janssen <spencerjanssen at gmail.com>**20090116210315
> Ignore-this: 4e15b7f3fd6af3b7317449608f5246b0
> ]
> [Update to my config
> Spencer Janssen <spencerjanssen at gmail.com>**20090116204553
> Ignore-this: 81017fa5b99855fc8ed1fe8892929f53
> ]
> [Adjustments to new userCode function
> Daniel Schoepe <asgaroth_ at gmx.de>**20090110221310]
> [X.U.EZConfig: expand documentation
> Brent Yorgey <byorgey at cis.upenn.edu>**20090116153143]
> [add a bit of documentation to HintedTile
> Brent Yorgey <byorgey at cis.upenn.edu>**20090114065126]
> [ManageHelpers: add isDialog
> johanngiwer at web.de**20090108232505]
> [CenteredMaster
> portnov84 at rambler.ru**20090111134513
>
> centerMaster layout modifier places master window at top of other, at center of screen. Other windows are managed by base layout.
> topRightMaster is similar, but places master window at top right corner.
> ]
> [XMonad.Util.XSelection: update maintainer information
> gwern0 at gmail.com**20090110213000
> Ignore-this: 1592ba07f2ed5d2258c215c2d175190a
> ]
> [X.U.XSelection: get rid of warning about missing newline, add Haddock link
> Brent Yorgey <byorgey at cis.upenn.edu>**20090102194357]
> [adds haddock documentation for transformPromptSelection
> loupgaroublond at gmail.com**20090102190954
>
> also renames the function per mailing list recommendation
> ]
> [adds a weird function to XSelection
> loupgaroublond at gmail.com**20081222020730
>
> This enables you to pass a function of (String -> String) to a selection function to modify the string before executing it. This way, you can input your own escape routines to make it shell command line safe, and/or do other fancier things.
> ]
> [ThreeColumnsMiddle
> xmonad at c-otto.de**20090102091019]
> [fix-fromJust-errors
> rupa at lrrr.us**20081224045509
>
> bogner wrote all this stuff and i just tested it.
>
> I had:
>
> myLogHook = ewmhDesktopLogHookCustom ScratchpadFilterOutWorkspace >> updatePointer Nearest
>
> Everytime I invoked or hid Scratchpad, it would leave a 'Maybe.fromJust: Nothing' line in .xsession-errors, and updatePointer would stop working.
>
> ]
> [ Prompt: Change Filemode to 600 for history-file (fixes bug 244)
> Dominik Bruhn <dominik at dbruhn.de>**20081218001601]
> [X.L.Monitor: changes in message passing
> Roman Cheplyaka <roma at ro-che.info>**20081226220851
> - transform mbName (Maybe String) to name (String)
> - slghtly change semantics of messages, document it
> ]
> [X.L.Monitor: change interface
> Roman Cheplyaka <roma at ro-che.info>**20081226213118
> - remove add*Monitor
> - add manageMonitor, monitor template
> ]
> [X.U.WindowProperties: propertyToQuery+docs
> Roman Cheplyaka <roma at ro-che.info>**20081225080702]
> [X.L.Monitor: docs
> Roman Cheplyaka <roma at ro-che.info>**20081225073904]
> [hlintify XUtils, XSelection, Search, WindowGo
> gwern0 at gmail.com**20081220153302
> Ignore-this: 7e877484e3cd8954b74232ea83180fa9
> ]
> [fix focus issue for XMonad.Actions.Warp.banishScreen
> Norbert Zeh <nzeh at cs.dal.ca>**20081212203532
>
> This patch ensures that the focus (or in fact the whose windowset)
> does not change as a result of a banishScreen. The way this is implemented
> will become problematic if xmonad ever goes multithreaded.
> ]
> [addition of XMonad.Actions.Warp.banishScreen
> Norbert Zeh <nzeh at cs.dal.ca>**20081212192621
>
> This works on top of warpToScreen and, thus, suffers from the same issue:
> focus change.
> ]
> [fixed documentation for banish
> Norbert Zeh <nzeh at cs.dal.ca>**20081212191819
>
> banish actually warps to the specified corner of the current window, not
> the screen.
> ]
> [addition of combined TallGrid layout
> Norbert Zeh <nzeh at cs.dal.ca>**20081212184836
>
> Added a module XMonad.Layouts.GridVariants, which defines layouts
> Grid and TallGrid. The former is a customizable version of Grid. The latter
> is a combination of Grid and Tall (see doc of the module).
> ]
> [Add FixedColumn, a layout like Tall but based on the resize hints of windows
> Justin Bogner <mail at justinbogner.com>**20081213073054]
> [XMonad.Actions.WindowGo: fix a floating-related focus bug
> gwern0 at gmail.com**20081205150755
> Ignore-this: c8b6625aa2bd4136937acbd2ad64ffd3
> If a floating window was focused, a cross-workspace 'raise' would cause a loop of
> shifting windows. Apparently the problem was 'focus' and its mouse-handling. Spencer
> suggested that the calls to focus be replaced with 'focusWindow', which resolved it.
> ]
> [Prompt.hs: +greenXPConfig and amberXPConfig
> gwern0 at gmail.com**20081119213122
> Ignore-this: 95ac7dbe9c8fe3618135966f251f4fc6
> ]
> [Prompt.hs: increase font size to 12 from niggardly 10
> gwern0 at gmail.com**20081119212523
> Ignore-this: 74a6e1ac5e1774da4ffc7c6667c034c
> ]
> [Prompt.hs: replace magic numbers with understandable names
> gwern0 at gmail.com**20081119212502
> Ignore-this: 8401c0213be9a32c925e1bd0ba5e01f1
> ]
> [X.L.Monitor: recommend doHideIgnore (docs)
> Roman Cheplyaka <roma at ro-che.info>**20081215190710]
> [X.L.Monitor: docs
> Roman Cheplyaka <roma at ro-che.info>**20081215184423]
> [X.L.Monitor: export Monitor datatype
> Roman Cheplyaka <roma at ro-che.info>**20081215184318]
> [X.H.ManageHelpers: add doHideIgnore
> Roman Cheplyaka <roma at ro-che.info>**20081215182758]
> [Add KDE 4 config, thanks to Shirakawasuna on IRC
> Spencer Janssen <spencerjanssen at gmail.com>**20081211071141
> Ignore-this: 51698961ab5b6e569c294d174f2804a9
> ]
> [I use the deleteConsecutive history filter
> Spencer Janssen <spencerjanssen at gmail.com>**20081025070438]
> [Remove XMonad.Config.PlainConfig, it has been turned into the separate xmonad-light project.
> Braden Shepherdson <Braden.Shepherdson at gmail.com>**20081203161534]
> [XMonad.Prompt: swap up and down per bug #243
> gwern0 at gmail.com**20081203013323
> Ignore-this: 8ab0481a0da7a983f501ac2fec4a68e8
> ]
> [Fix boolean operator precedence in GridSelect keybindings
> Aleksandar Dimitrov <aleks.dimitrov at googlemail.com>**20081201120928
> The vim-like hjkl keys were ORed to the key event AND arrow keys.
> ]
> [GridSelect.hs: navigate grid with h,j,k,l as well as arrow keys
> sean.escriva at gmail.com**20081122084725]
> [Export setOpacity from FadeInactive. Document how to make monitor transparent (X.L.Monitor)
> Roman Cheplyaka <roma at ro-che.info>**20081117153027]
> [Monitor: use broadcastMessage instead of sendMessage; this solves several issues
> Roman Cheplyaka <roma at ro-che.info>**20081117133957]
> [FadeInactive: fade all inactive windows (including focused windows on visible screens)
> Roman Cheplyaka <roma at ro-che.info>**20081117130115]
> [Monitor: documented one more issue
> Roman Cheplyaka <roma at ro-che.info>**20081117113807]
> [Monitor: improved the docs
> Roman Cheplyaka <roma at ro-che.info>**20081117073709]
> [added XMonad.Layout.Monitor
> Roman Cheplyaka <roma at ro-che.info>**20081115104735]
> [WindowProperties: added allWithProperty
> Roman Cheplyaka <roma at ro-che.info>**20081115104525]
> [ManageHelpers: added doSideFloat (generalization of doCenterFloat)
> Roman Cheplyaka <roma at ro-che.info>**20081114113015]
> [GridSelect: Export default_colorizer
> Dominik Bruhn <dominik at dbruhn.de>**20081112140005]
> [Simplify code for restriction-calculation and remove compiletime warnings
> Dominik Bruhn <dominik at dbruhn.de>**20081112134630]
> [Simplify handle/eventLoop, introduce findInWindowMap, partial updates for key movements (less flickering)
> Clemens Fruhwirth <clemens at endorphin.org>**20081111100405
>
> * handle/eventLoop carried the display and the drawing window as
> parameters. The display is available from the embedded X monad, the
> drawing windows was added.
>
> * updateWindows now takes a list of windows to
> update. updateAllWindows updates all windows.
>
> * only the windows that are modified by key movements are redrawn
> now. This means less flickering.
>
> ]
> [GridSelect: force cursor stay in visible area
> Roman Cheplyaka <roma at ro-che.info>**20081111063348]
> [GridSelect: fix infiniteness problem with diamondRestrict
> Roman Cheplyaka <roma at ro-che.info>**20081111055350]
> [GridSelect: remove tabs
> Roman Cheplyaka <roma at ro-che.info>**20081111053647]
> [Exported shrinkWhile from Decoration to use in GridSelect
> Roman Cheplyaka <roma at ro-che.info>**20081110191534]
> [GridSelect: added link to a screenshot
> Roman Cheplyaka <roma at ro-che.info>**20081110190617]
> [GridSelect: various improvements
> Roman Cheplyaka <roma at ro-che.info>**20081110184644
> Added documentation
> Restricted export list for the sake of haddock
> Added functions:
> withSelectedWindow
> bringSelected (by Clemens Fruhwirth)
> goToSelected (by Dominik Bruhn)
> ]
> [Initial version of GridSelect.hs with a lot room for improvement/cleanups
> Clemens Fruhwirth <clemens at endorphin.org>**20081107115114]
> [documentation: XMonad.Util.Search.hs, add EZConfig keybindings example
> sean.escriva at gmail.com**20081106171707]
> [typo
> Don Stewart <dons at galois.com>**20081104043044
> Ignore-this: bdac0ff3316c821bce321b51c62f6e89
> ]
> [place an upper bound on the version of base we support
> Don Stewart <dons at galois.com>**20081104035857
> Ignore-this: 29139cc4f0ecb299b56ae99f7d20b854
> ]
> [explicit import list for things in the process library
> Don Stewart <dons at galois.com>**20081104035319
> Ignore-this: 91b7f96421828788760e8bcff7dec317
> ]
> [Work around ghc 6.10 bug #2738
> Don Stewart <dons at galois.com>**20081104034819
> Ignore-this: c75da9693fa642025eac0d074869423d
> ]
> [windowPromptBringCopy
> deadguysfrom at gmail.com**20081023173019]
> [generic menu and window bringer
> Travis B. Hartwell <nafai at travishartwell.net>**20081027005523]
> [Search.hs: +hackage search, courtesy of byorgey
> gwern0 at gmail.com**20081031214937
> Ignore-this: 24db0ceed49f8bd37ce98ccf8f8ca2ab
> ]
> [Prompt.hs rename deleteConsecutiveDuplicates
> gwern0 at gmail.com**20081008205131
> That name is really unwieldy and long.
> ]
> [Prompt.hs: have historyCompletion filter dupes
> gwern0 at gmail.com**20081008204710
> Specifically, it calls deleteConsecutiveDuplicates on the end product. uniqSort reverses order in an unfortunate way, so we don't use that.
> The use-case is when a user has added the same input many times - as it stands, if the history records 30 'top's or whatever, the completion will show 30 'top' entries! This fixes that.
> ]
> [Prompt.hs: tweak haddocks
> gwern0 at gmail.com**20081008204649]
> [Prompt.hs: mv uniqSort to next to its confreres, and mention the trade-off
> gwern0 at gmail.com**20081008192645]
> [Do not consider XMONAD_TIMER unknown
> Joachim Breitner <mail at joachim-breitner.de>**20081008195643]
> [Kill window without focusing it first
> Joachim Breitner <mail at joachim-breitner.de>**20081005002533
> This patch requires the patch "add killWindow function" in xmonad.
> Before this patch, people would experience “workspace flicker” when closing
> a window via EWMH that is not on the current workspace, for example when
> quitting pidgin via the panel icon.
> ]
> [let MagnifyLess actually magnify less
> daniel at wagner-home.com**20081015153911]
> [Actions.Search: add a few search engines
> intrigeri at boum.org**20081008104033
>
> Add Debian {package, bug, tracking system} search engines, as well as Google
> Images and isohunt.
>
> ]
> [Implement HiddenNonEmptyWS with HiddenWS and NonEmptyWS
> Joachim Breitner <mail at joachim-breitner.de>**20081006211027
> (Just to reduce code duplication)
> ]
> [Add straightforward HiddenWS to WSType
> Joachim Breitner <mail at joachim-breitner.de>**20081006210548
> With NonEmptyWS and HiddenNonEmptyWS present, HiddenWS is obviously missing.
> ]
> [Merge emptyLayoutMod into redoLayout
> Joachim Breitner <mail at joachim-breitner.de>**20081005190220
> This removes the emptyLayoutMod method from the LayoutModifier class, and
> change the Stack parameter to redoLayout to a Maybe Stack one. It also changes
> all affected code. This should should be a refactoring without any change in
> program behaviour.
> ]
> [SmartBorders even for empty layouts
> Joachim Breitner <mail at joachim-breitner.de>**20081005184426
> Fixes: http://code.google.com/p/xmonad/issues/detail?id=223
> ]
> [Paste.hs: improve haddocks
> gwern0 at gmail.com**20080927150158]
> [Paste.hs: fix haddock
> gwern0 at gmail.com**20080927145238]
> [minor explanatory comment
> daniel at wagner-home.com**20081003015919]
> [XMonad.Layout.HintedGrid: add GridRatio (--no-test because of haddock breakage)
> Lukas Mai <l.mai at web.de>**20080930141715]
> [XMonad.Util.Font: UTF8 -> USE_UTF8
> Lukas Mai <l.mai at web.de>**20080930140056]
> [Paste.hs: implement noModMask suggestion
> gwern0 at gmail.com**20080926232056]
> [fix a divide by zero error in Grid
> daniel at wagner-home.com**20080926204148]
> [-DUTF8 flag with -DUSE_UTF8
> gwern0 at gmail.com**20080921154014]
> [XSelection.hs: use CPP to compile against utf8-string
> gwern0 at gmail.com**20080920151615]
> [add XMonad.Config.Azerty
> Devin Mullins <me at twifkak.com>**20080924044946]
> [flip GridRatio to match convention (x/y)
> Devin Mullins <me at twifkak.com>**20080922033354]
> [let Grid have a configurable aspect ratio goal
> daniel at wagner-home.com**20080922010950]
> [Paste.hs: +warning about ASCII limitations
> gwern0 at gmail.com**20080921155038]
> [Paste.hs: shorten comment lines to under 80 columns per sjanssen
> gwern0 at gmail.com**20080921154950]
> [Forgot to enable historyFilter :(
> Spencer Janssen <spencerjanssen at gmail.com>**20080921094254]
> [Prompt: add configurable history filters
> Spencer Janssen <spencerjanssen at gmail.com>**20080921093453]
> [Update my config to use 'statusBar'
> Spencer Janssen <spencerjanssen at gmail.com>**20080921063513]
> [Rename pasteKey functions to sendKey
> Spencer Janssen <spencerjanssen at gmail.com>**20080921062016]
> [DynamicLog: doc fixes
> Spencer Janssen <spencerjanssen at gmail.com>**20080921061314]
> [Move XMonad.Util.XPaste to XMonad.Util.Paste
> Spencer Janssen <spencerjanssen at gmail.com>**20080921060947]
> [Depend on X11 >= 1.4.3
> Spencer Janssen <spencerjanssen at gmail.com>**20080921055456]
> [statusBar now supplies the action to toggle struts
> Spencer Janssen <spencerjanssen at gmail.com>**20080918013858]
> [cleanup - use currentTag
> Devin Mullins <me at twifkak.com>**20080921011159]
> [XPaste.hs: improve author info
> gwern0 at gmail.com**20080920152342]
> [+XMonad.Util.XPaste: a module for pasting strings to windows
> gwern0 at gmail.com**20080920152106]
> [UrgencyHook bug fix: cleanupUrgents should clean up reminders, too
> Devin Mullins <me at twifkak.com>**20080920062117]
> [Sketch of XMonad.Config.Monad
> Spencer Janssen <spencerjanssen at gmail.com>**20080917081838]
> [raiseMaster
> seanmce33 at gmail.com**20080912184830]
> [Add missing space between dzen command and flags
> Daniel Neri <daniel.neri at sigicom.com>**20080915131009]
> [Big DynamicLog refactor. Added statusBar, improved compositionality for dzen and xmobar
> Spencer Janssen <spencerjanssen at gmail.com>**20080913205931
> Compatibility notes:
> - dzen type change
> - xmobar type change
> - dynamicLogDzen removed
> - dynamicLogXmobar removed
> ]
> [Take maintainership of XMonad.Prompt
> Spencer Janssen <spencerjanssen at gmail.com>**20080911230442]
> [Overhaul Prompt to use a zipper for history navigation. Fixes issue #216
> Spencer Janssen <spencerjanssen at gmail.com>**20080911225940]
> [Use the new completion on tab setting
> Spencer Janssen <spencerjanssen at gmail.com>**20080911085940]
> [Only start to show the completion window with more than one match
> Joachim Breitner <mail at joachim-breitner.de>**20080908110129]
> [XPrompt: Add showCompletionOnTab option
> Joachim Breitner <mail at joachim-breitner.de>**20080908105758
> This patch partially implements
> http://code.google.com/p/xmonad/issues/detail?id=215
> It adds a XPConfig option that, if enabled, hides the completion window
> until the user presses Tab once. Default behaviour is preserved.
> TODO: If Tab causes a unique completion, continue to hide the completion
> window.
> ]
> [XMonad.Actions.Plane.planeKeys: function to make easier to configure
> Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080714153601]
> [XMonad.Actions.Plane: removed unneeded hiding
> Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080714152631]
> [Improvements in documentation
> Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080709002425]
> [Fix haddock typos in XMonad.Config.{Desktop,Gnome,Kde}
> Spencer Janssen <spencerjanssen at gmail.com>**20080911040808]
> [add clearUrgents for your keys
> Devin Mullins <me at twifkak.com>**20080909055425]
> [add reminder functionality to UrgencyHook
> Devin Mullins <me at twifkak.com>**20080824200548
> I'm considering rewriting remindWhen and suppressWhen as UrgencyHookModifiers, so to speak. Bleh.
> ]
> [TAG 0.8
> Spencer Janssen <spencerjanssen at gmail.com>**20080905195420]
> Patch bundle hash:
> 2bba26eb313b67bbefdda14f4f91386e6c546b65
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
More information about the xmonad
mailing list