{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
module XMonad.Actions.TreeSelect
(
treeselectWorkspace
, toWorkspaces
, treeselectAction
, Pixel
, TSConfig(..)
, tsDefaultConfig
, defaultNavigation
, select
, cancel
, moveParent
, moveChild
, moveNext
, movePrev
, moveHistBack
, moveHistForward
, moveTo
, TSNode(..)
, treeselect
, treeselectAt
) where
import Control.Applicative
import Control.Monad.Reader
import Control.Monad.State
import Data.List (find)
import Data.Maybe
import Data.Tree
import Foreign
import System.IO
import System.Posix.Process (forkProcess, executeFile)
import XMonad hiding (liftX)
import XMonad.StackSet as W
import XMonad.Util.Font
import XMonad.Util.NamedWindows
import XMonad.Util.TreeZipper
import XMonad.Hooks.WorkspaceHistory
import qualified Data.Map as M
#ifdef XFT
import Graphics.X11.Xft
import Graphics.X11.Xrender
#endif
data TSConfig a = TSConfig { ts_hidechildren :: Bool
, ts_background :: Pixel
, ts_font :: String
, ts_node :: (Pixel, Pixel)
, ts_nodealt :: (Pixel, Pixel)
, ts_highlight :: (Pixel, Pixel)
, ts_extra :: Pixel
, ts_node_width :: Int
, ts_node_height :: Int
, ts_originX :: Int
, ts_originY :: Int
, ts_indent :: Int
, ts_navigate :: M.Map (KeyMask, KeySym) (TreeSelect a (Maybe a))
}
instance Default (TSConfig a) where
def = TSConfig { ts_hidechildren = True
, ts_background = 0xc0c0c0c0
, ts_font = "xft:Sans-16"
, ts_node = (0xff000000, 0xff50d0db)
, ts_nodealt = (0xff000000, 0xff10b8d6)
, ts_highlight = (0xffffffff, 0xffff0000)
, ts_extra = 0xff000000
, ts_node_width = 200
, ts_node_height = 30
, ts_originX = 0
, ts_originY = 0
, ts_indent = 80
, ts_navigate = defaultNavigation
}
defaultNavigation :: M.Map (KeyMask, KeySym) (TreeSelect a (Maybe a))
defaultNavigation = M.fromList
[ ((0, xK_Escape), cancel)
, ((0, xK_Return), select)
, ((0, xK_space), select)
, ((0, xK_Up), movePrev)
, ((0, xK_Down), moveNext)
, ((0, xK_Left), moveParent)
, ((0, xK_Right), moveChild)
, ((0, xK_k), movePrev)
, ((0, xK_j), moveNext)
, ((0, xK_h), moveParent)
, ((0, xK_l), moveChild)
, ((0, xK_o), moveHistBack)
, ((0, xK_i), moveHistForward)
]
tsDefaultConfig :: TSConfig a
tsDefaultConfig = def
data TSNode a = TSNode { tsn_name :: String
, tsn_extra :: String
, tsn_value :: a
}
data TSState a = TSState { tss_tree :: TreeZipper (TSNode a)
, tss_window :: Window
, tss_display :: Display
, tss_size :: (Int, Int)
, tss_xfont :: XMonadFont
, tss_gc :: GC
, tss_visual :: Visual
, tss_colormap :: Colormap
, tss_history :: ([[String]], [[String]])
}
newtype TreeSelect a b = TreeSelect { runTreeSelect :: ReaderT (TSConfig a) (StateT (TSState a) X) b }
deriving (Monad, Applicative, Functor, MonadState (TSState a), MonadReader (TSConfig a), MonadIO)
liftX :: X a -> TreeSelect b a
liftX = TreeSelect . lift . lift
treeselect :: TSConfig a
-> Forest (TSNode a)
-> X (Maybe a)
treeselect c t = treeselectAt c (fromForest t) []
treeselectAt :: TSConfig a
-> TreeZipper (TSNode a)
-> [[String]]
-> X (Maybe a)
treeselectAt conf@TSConfig{..} zipper hist = withDisplay $ \display -> do
rootw <- asks theRoot
Rectangle{..} <- gets $ screenRect . W.screenDetail . W.current . windowset
Just vinfo <- liftIO $ matchVisualInfo display (defaultScreen display) 32 4
colormap <- liftIO $ createColormap display rootw (visualInfo_visual vinfo) allocNone
win <- liftIO $ allocaSetWindowAttributes $ \attributes -> do
set_override_redirect attributes True
set_colormap attributes colormap
set_background_pixel attributes ts_background
set_border_pixel attributes 0
createWindow display rootw rect_x rect_y rect_width rect_height 0 (visualInfo_depth vinfo) inputOutput (visualInfo_visual vinfo) (cWColormap .|. cWBorderPixel .|. cWBackPixel) attributes
liftIO $ do
mapWindow display win
selectInput display win (exposureMask .|. keyPressMask .|. buttonReleaseMask)
grabButton display button1 anyModifier win True buttonReleaseMask grabModeAsync grabModeAsync none none
status <- liftIO $ grabKeyboard display win True grabModeAsync grabModeAsync currentTime
r <- if status == grabSuccess
then do
gc <- liftIO $ createGC display win
xfont <- initXMF ts_font
ret <- evalStateT (runReaderT (runTreeSelect (redraw >> navigate)) conf)
TSState{ tss_tree = zipper
, tss_window = win
, tss_display = display
, tss_xfont = xfont
, tss_size = (fromIntegral rect_width, fromIntegral rect_height)
, tss_gc = gc
, tss_visual = visualInfo_visual vinfo
, tss_colormap = colormap
, tss_history = ([], hist)
}
releaseXMF xfont
liftIO $ freeGC display gc
return ret
else return Nothing
liftIO $ do
unmapWindow display win
destroyWindow display win
freeColormap display colormap
sync display False
return r
treeselectWorkspace :: TSConfig WorkspaceId
-> Forest String
-> (WorkspaceId -> WindowSet -> WindowSet)
-> X ()
treeselectWorkspace c xs f = do
ws <- gets (W.workspaces . windowset)
if all (`elem` map tag ws) (toWorkspaces xs)
then do
wsf <- forMForest (mkPaths xs) $ \(n, i) -> maybe (return (TSNode n "Does not exist!" "")) (mkNode n) (find (\w -> i == tag w) ws)
me <- gets (W.tag . W.workspace . W.current . windowset)
hist <- workspaceHistory
treeselectAt c (fromJust $ followPath tsn_name (splitPath me) $ fromForest wsf) (map splitPath hist) >>= maybe (return ()) (windows . f)
else liftIO $ do
let msg = unlines $ [ "Please add:"
, " workspaces = toWorkspaces myWorkspaces"
, "to your XMonad config!"
, ""
, "XConfig.workspaces: "
] ++ map tag ws
hPutStrLn stderr msg
_ <- forkProcess $ executeFile "xmessage" True [msg] Nothing
return ()
where
mkNode n w = do
name <- maybe (return "") (fmap show . getName . W.focus) $ stack w
return $ TSNode n name (tag w)
toWorkspaces :: Forest String -> [WorkspaceId]
toWorkspaces = map snd . concatMap flatten . mkPaths
mkPaths :: Forest String -> Forest (String, WorkspaceId)
mkPaths = map (\(Node n ns) -> Node (n, n) (map (f n) ns))
where
f pth (Node x xs) = let pth' = pth ++ '.' : x
in Node (x, pth') (map (f pth') xs)
splitPath :: WorkspaceId -> [String]
splitPath i = case break (== '.') i of
(x, []) -> [x]
(x, _:xs) -> x : splitPath xs
treeselectAction :: TSConfig (X a) -> Forest (TSNode (X a)) -> X ()
treeselectAction c xs = treeselect c xs >>= \x -> case x of
Just a -> a >> return ()
Nothing -> return ()
forMForest :: (Functor m, Applicative m, Monad m) => [Tree a] -> (a -> m b) -> m [Tree b]
forMForest x g = mapM (mapMTree g) x
mapMTree :: (Functor m, Applicative m, Monad m) => (a -> m b) -> Tree a -> m (Tree b)
mapMTree f (Node x xs) = Node <$> f x <*> mapM (mapMTree f) xs
select :: TreeSelect a (Maybe a)
select = Just <$> gets (tsn_value . cursor . tss_tree)
cancel :: TreeSelect a (Maybe a)
cancel = return Nothing
moveParent :: TreeSelect a (Maybe a)
moveParent = moveWith parent >> redraw >> navigate
moveChild :: TreeSelect a (Maybe a)
moveChild = moveWith children >> redraw >> navigate
moveNext :: TreeSelect a (Maybe a)
moveNext = moveWith nextChild >> redraw >> navigate
movePrev :: TreeSelect a (Maybe a)
movePrev = moveWith previousChild >> redraw >> navigate
moveHistBack :: TreeSelect a (Maybe a)
moveHistBack = do
s <- get
case tss_history s of
(xs, a:y:ys) -> do
put s{tss_history = (a:xs, y:ys)}
moveTo y
_ -> navigate
moveHistForward :: TreeSelect a (Maybe a)
moveHistForward = do
s <- get
case tss_history s of
(x:xs, ys) -> do
put s{tss_history = (xs, x:ys)}
moveTo x
_ -> navigate
moveTo :: [String]
-> TreeSelect a (Maybe a)
moveTo i = moveWith (followPath tsn_name i . rootNode) >> redraw >> navigate
moveWith :: (TreeZipper (TSNode a) -> Maybe (TreeZipper (TSNode a))) -> TreeSelect a ()
moveWith f = do
s <- get
case f (tss_tree s) of
Just t -> put s{ tss_tree = t }
Nothing -> return ()
navigate :: TreeSelect a (Maybe a)
navigate = gets tss_display >>= \d -> join . liftIO . allocaXEvent $ \e -> do
maskEvent d (exposureMask .|. keyPressMask .|. buttonReleaseMask) e
ev <- getEvent e
if ev_event_type ev == keyPress
then do
(ks, _) <- lookupString $ asKeyEvent e
return $ do
mask <- liftX $ cleanMask (ev_state ev)
f <- asks ts_navigate
fromMaybe navigate $ M.lookup (mask, fromMaybe xK_VoidSymbol ks) f
else return navigate
redraw :: TreeSelect a ()
redraw = do
win <- gets tss_window
dpy <- gets tss_display
liftIO $ clearWindow dpy win
t <- gets tss_tree
_ <- drawLayers 0 0 (reverse $ (tz_before t, cursor t, tz_after t) : tz_parents t)
return ()
drawLayers :: Int
-> Int
-> [(Forest (TSNode a), TSNode a, Forest (TSNode a))]
-> TreeSelect a Int
drawLayers _ yl [] = return yl
drawLayers xl yl ((bs, c, as):xs) = do
TSConfig{..} <- ask
let nodeColor y = if odd y then ts_node else ts_nodealt
forM_ (zip [yl ..] (reverse bs)) $ \(y, Node n _) ->
drawNode xl y n (nodeColor y)
let current_level = yl + length bs
drawNode xl current_level c $
if null xs then ts_highlight
else nodeColor current_level
l2 <- drawLayers (xl + 1) (current_level + 1) xs
forM_ (zip [l2 ..] as) $ \(y, Node n _) ->
drawNode xl y n (nodeColor y)
return (l2 + length as)
drawNode :: Int
-> Int
-> TSNode a
-> (Pixel, Pixel)
-> TreeSelect a ()
drawNode ix iy TSNode{..} col = do
TSConfig{..} <- ask
window <- gets tss_window
display <- gets tss_display
font <- gets tss_xfont
gc <- gets tss_gc
colormap <- gets tss_colormap
visual <- gets tss_visual
liftIO $ drawWinBox window display visual colormap gc font col tsn_name ts_extra tsn_extra
(ix * ts_indent) (iy * ts_node_height)
ts_node_width ts_node_height
drawWinBox :: Window -> Display -> Visual -> Colormap -> GC -> XMonadFont -> (Pixel, Pixel) -> String -> Pixel -> String -> Int -> Int -> Int -> Int -> IO ()
drawWinBox win display visual colormap gc font (fg, bg) text fg2 text2 x y w h = do
setForeground display gc bg
fillRectangle display win gc (fromIntegral x) (fromIntegral y) (fromIntegral w) (fromIntegral h)
drawStringXMF display win visual colormap gc font fg
(fromIntegral $ x + 8)
(fromIntegral $ y + h - 8)
text
drawStringXMF display win visual colormap gc font fg2
(fromIntegral $ x + w + 8)
(fromIntegral $ y + h - 8)
text2
drawStringXMF :: Display -> Drawable -> Visual -> Colormap -> GC
-> XMonadFont
-> Pixel
-> Position
-> Position
-> String
-> IO ()
drawStringXMF display window visual colormap gc font col x y text = case font of
Core fnt -> do
setForeground display gc col
setFont display gc $ fontFromFontStruct fnt
drawImageString display window gc x y text
Utf8 fnt -> do
setForeground display gc col
wcDrawImageString display window fnt gc x y text
#ifdef XFT
Xft fnt -> do
withXftDraw display window visual colormap $
\ft_draw -> withXftColorValue display visual colormap (fromARGB col) $
\ft_color -> xftDrawString ft_draw ft_color fnt x y text
fromARGB :: Pixel -> XRenderColor
fromARGB x = XRenderColor (fromIntegral $ 0xff00 .&. shiftR x 8)
(fromIntegral $ 0xff00 .&. x)
(fromIntegral $ 0xff00 .&. shiftL x 8)
(fromIntegral $ 0xff00 .&. shiftR x 16)
#endif