mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
X.Prompt: Remove non-IORef complWin
While it is true that we need an IORef complWin in case of an exception, so the window can be destroyed correctly, we do not need its non-IORef counterpart at all. When we need to access the complWin it's undoubtably when we want to do _something_ with regards to window management; these things naturally live in `XP ()` and so there's not loss of purity with this change.
This commit is contained in:
parent
84dcc9b716
commit
5bc0d9d777
@ -5,6 +5,7 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Prompt
|
-- Module : XMonad.Prompt
|
||||||
@ -132,15 +133,12 @@ data XPState =
|
|||||||
, rootw :: !Window
|
, rootw :: !Window
|
||||||
, win :: !Window
|
, win :: !Window
|
||||||
, screen :: !Rectangle
|
, screen :: !Rectangle
|
||||||
, complWin :: Maybe Window
|
|
||||||
, complWinDim :: Maybe ComplWindowDim
|
, complWinDim :: Maybe ComplWindowDim
|
||||||
, complIndex :: !(Int,Int)
|
, complIndex :: !(Int,Int)
|
||||||
-- | This IORef should always have the same value as
|
, complWin :: IORef (Maybe Window)
|
||||||
-- complWin. Its purpose is to enable removal of the
|
-- ^ This is an 'IORef' to enable removal of the completion
|
||||||
-- completion window if an exception occurs, since the most
|
-- window if an exception occurs, since otherwise the most
|
||||||
-- recent value of complWin is not available when handling
|
-- recent value of 'complWin' would not be available.
|
||||||
-- exceptions.
|
|
||||||
, complWinRef :: IORef (Maybe Window)
|
|
||||||
, showComplWin :: Bool
|
, showComplWin :: Bool
|
||||||
, operationMode :: XPOperationMode
|
, operationMode :: XPOperationMode
|
||||||
, highlightedCompl :: Maybe String
|
, highlightedCompl :: Maybe String
|
||||||
@ -363,9 +361,8 @@ initState d rw w s opMode gc fonts h c nm =
|
|||||||
, rootw = rw
|
, rootw = rw
|
||||||
, win = w
|
, win = w
|
||||||
, screen = s
|
, screen = s
|
||||||
, complWin = Nothing
|
|
||||||
, complWinDim = Nothing
|
, complWinDim = Nothing
|
||||||
, complWinRef = unsafePerformIO (newIORef Nothing)
|
, complWin = unsafePerformIO (newIORef Nothing)
|
||||||
, showComplWin = not (showCompletionOnTab c)
|
, showComplWin = not (showCompletionOnTab c)
|
||||||
, operationMode = opMode
|
, operationMode = opMode
|
||||||
, highlightedCompl = Nothing
|
, highlightedCompl = Nothing
|
||||||
@ -620,7 +617,7 @@ runXP st = do
|
|||||||
updateWindows
|
updateWindows
|
||||||
eventLoop handleMain evDefaultStop)
|
eventLoop handleMain evDefaultStop)
|
||||||
st
|
st
|
||||||
`finally` (mapM_ (destroyWindow d) =<< readIORef (complWinRef st))
|
`finally` (mapM_ (destroyWindow d) =<< readIORef (complWin st))
|
||||||
`finally` sync d False)
|
`finally` sync d False)
|
||||||
|
|
||||||
type KeyStroke = (KeySym, String)
|
type KeyStroke = (KeySym, String)
|
||||||
@ -1405,6 +1402,13 @@ createPromptWin dpy rootw XPC{ position, height } scn = do
|
|||||||
CenteredAt _ w -> floor $ fi (rect_width scn) * w
|
CenteredAt _ w -> floor $ fi (rect_width scn) * w
|
||||||
_ -> rect_width scn
|
_ -> rect_width scn
|
||||||
|
|
||||||
|
-- | Update the state of the completion window.
|
||||||
|
updateComplWin :: Maybe Window -> Maybe ComplWindowDim -> XP ()
|
||||||
|
updateComplWin win winDim = do
|
||||||
|
cwr <- gets complWin
|
||||||
|
io $ writeIORef cwr win
|
||||||
|
modify' (\s -> s { complWinDim = winDim })
|
||||||
|
|
||||||
--- | Update all prompt windows.
|
--- | Update all prompt windows.
|
||||||
updateWindows :: XP ()
|
updateWindows :: XP ()
|
||||||
updateWindows = redrawWindows (void destroyComplWin) =<< getCompletions
|
updateWindows = redrawWindows (void destroyComplWin) =<< getCompletions
|
||||||
@ -1449,7 +1453,7 @@ redrawComplWin compl = do
|
|||||||
w <- createComplWin nwi
|
w <- createComplWin nwi
|
||||||
drawComplWin w compl
|
drawComplWin w compl
|
||||||
if compl /= [] && showComplWin
|
if compl /= [] && showComplWin
|
||||||
then case complWin of
|
then io (readIORef complWin) >>= \case
|
||||||
Just w -> case complWinDim of
|
Just w -> case complWinDim of
|
||||||
Just wi -> if nwi == wi -- complWinDim did not change
|
Just wi -> if nwi == wi -- complWinDim did not change
|
||||||
then drawComplWin w compl -- so update
|
then drawComplWin w compl -- so update
|
||||||
@ -1460,14 +1464,11 @@ redrawComplWin compl = do
|
|||||||
where
|
where
|
||||||
createComplWin :: ComplWindowDim -> XP Window
|
createComplWin :: ComplWindowDim -> XP Window
|
||||||
createComplWin wi@ComplWindowDim{ cwX, cwY, cwWidth, cwRowHeight } = do
|
createComplWin wi@ComplWindowDim{ cwX, cwY, cwWidth, cwRowHeight } = do
|
||||||
XPS{ dpy, rootw, complWinRef } <- get
|
XPS{ dpy, rootw } <- get
|
||||||
let scr = defaultScreenOfDisplay dpy
|
let scr = defaultScreenOfDisplay dpy
|
||||||
w <- io $ mkUnmanagedWindow dpy scr rootw cwX cwY cwWidth cwRowHeight
|
w <- io $ mkUnmanagedWindow dpy scr rootw cwX cwY cwWidth cwRowHeight
|
||||||
io $ mapWindow dpy w
|
io $ mapWindow dpy w
|
||||||
-- Update the IORef
|
updateComplWin (Just w) (Just wi)
|
||||||
io $ writeIORef complWinRef (Just w)
|
|
||||||
-- Set the completion window to the just created one
|
|
||||||
modify (\s -> s { complWin = Just w, complWinDim = Just wi })
|
|
||||||
return w
|
return w
|
||||||
|
|
||||||
-- | Print the main part of the prompt: the prompter, as well as the
|
-- | Print the main part of the prompt: the prompter, as well as the
|
||||||
@ -1517,11 +1518,10 @@ getCompletions = do
|
|||||||
-- | Destroy the currently drawn completion window, if there is one.
|
-- | Destroy the currently drawn completion window, if there is one.
|
||||||
destroyComplWin :: XP ()
|
destroyComplWin :: XP ()
|
||||||
destroyComplWin = do
|
destroyComplWin = do
|
||||||
XPS{ dpy, complWin, complWinRef } <- get
|
XPS{ dpy, complWin } <- get
|
||||||
case complWin of
|
io (readIORef complWin) >>= \case
|
||||||
Just w -> do io $ destroyWindow dpy w
|
Just w -> do io $ destroyWindow dpy w
|
||||||
io $ writeIORef complWinRef Nothing
|
updateComplWin Nothing Nothing
|
||||||
modify (\s -> s { complWin = Nothing, complWinDim = Nothing })
|
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
|
|
||||||
-- | Given the completions that we would like to show, calculate the
|
-- | Given the completions that we would like to show, calculate the
|
||||||
|
Loading…
x
Reference in New Issue
Block a user