Make minSize depend on the screen if necessary
This commit is contained in:
parent
4cc0f0f2ee
commit
581e1f9c63
7 changed files with 68 additions and 44 deletions
|
@ -60,9 +60,13 @@ instance WidgetClass Border where
|
|||
type WidgetData Border = BorderState
|
||||
initWidget (Border _ widgets) phi disp = liftM BorderState $ mapM (createWidgetState phi disp) widgets
|
||||
|
||||
minSize (Border config _) (BorderState widgetStates) height =
|
||||
max (borderH m+2*(bw+cr)) $ sum (map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height') widgetStates) + borderH p + 2*bw + borderH m
|
||||
minSize (Border config _) (BorderState widgetStates) height screen =
|
||||
case True of
|
||||
_ | childSize == 0 -> 0
|
||||
| otherwise -> max (borderH m+2*(bw+cr)) (childSize + borderH p + 2*bw + borderH m)
|
||||
where
|
||||
childSize = sum $ map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height' screen) widgetStates
|
||||
|
||||
m = margin config
|
||||
bw = borderWidth config
|
||||
p = padding config
|
||||
|
@ -71,7 +75,9 @@ instance WidgetClass Border where
|
|||
|
||||
weight (Border config _) = borderWeight config
|
||||
|
||||
layout (Border config _) (BorderState widgetStates) width height = BorderState $ layoutWidgets widgetStates x y width' height'
|
||||
layout (Border config _) (BorderState widgetStates) width height screen = case True of
|
||||
_ | width' > 0 -> BorderState $ layoutWidgets widgetStates x y width' height' screen
|
||||
| otherwise -> BorderState widgetStates
|
||||
where
|
||||
m = margin config
|
||||
bw = borderWidth config
|
||||
|
@ -82,10 +88,14 @@ instance WidgetClass Border where
|
|||
width' = width - borderH m - 2*bw - borderH p
|
||||
height' = height - borderV m - 2*bw - borderV p
|
||||
|
||||
render (Border config _) (BorderState widgetStates) w h screen = do
|
||||
render (Border config _) (BorderState widgetStates) w h screen = when (w > borderH m - 2*bw - borderH p) $ do
|
||||
drawBorder config 0 0 w h
|
||||
clip
|
||||
renderWidgets widgetStates screen
|
||||
where
|
||||
m = margin config
|
||||
bw = borderWidth config
|
||||
p = padding config
|
||||
|
||||
handleMessage _ (BorderState widgetStates) m = BorderState $ handleMessageWidgets m widgetStates
|
||||
|
||||
|
|
|
@ -64,13 +64,13 @@ class Show a => WidgetClass a where
|
|||
|
||||
initWidget :: a -> Phi -> Display -> IO (WidgetData a)
|
||||
|
||||
minSize :: a -> WidgetData a -> Int -> Int
|
||||
minSize :: a -> WidgetData a -> Int -> Xlib.Rectangle -> Int
|
||||
|
||||
weight :: a -> Float
|
||||
weight _ = 0
|
||||
|
||||
layout :: a -> WidgetData a -> Int -> Int -> WidgetData a
|
||||
layout _ priv _ _ = priv
|
||||
layout :: a -> WidgetData a -> Int -> Int -> Xlib.Rectangle -> WidgetData a
|
||||
layout _ priv _ _ _ = priv
|
||||
|
||||
render :: a -> WidgetData a -> Int -> Int -> Xlib.Rectangle -> Render ()
|
||||
|
||||
|
@ -101,10 +101,10 @@ createWidgetState phi disp (Widget w) = do
|
|||
, statePrivateData = priv
|
||||
}
|
||||
|
||||
layoutWidgets :: [WidgetState] -> Int -> Int -> Int -> Int -> [WidgetState]
|
||||
layoutWidgets widgets x y width height = snd $ mapAccumL layoutWidgetAndX x widgets
|
||||
layoutWidgets :: [WidgetState] -> Int -> Int -> Int -> Int -> Xlib.Rectangle -> [WidgetState]
|
||||
layoutWidgets widgets x y width height screen = snd $ mapAccumL layoutWidgetAndX x widgets
|
||||
where
|
||||
sizesum = sum $ map (\(WidgetState {stateWidget = w, statePrivateData = priv} ) -> nneg $ minSize w priv height) widgets
|
||||
sizesum = sum $ map (\(WidgetState {stateWidget = w, statePrivateData = priv} ) -> nneg $ minSize w priv height screen) widgets
|
||||
wsum = let wsum = sum $ map (\(WidgetState {stateWidget = w} ) -> nneg . weight $ w) widgets
|
||||
in if wsum > 0 then wsum else 1
|
||||
|
||||
|
@ -115,8 +115,8 @@ layoutWidgets widgets x y width height = snd $ mapAccumL layoutWidgetAndX x widg
|
|||
|
||||
layoutWidget wX state = case state of
|
||||
WidgetState {stateWidget = w, statePrivateData = priv} ->
|
||||
let wWidth = floor $ (fromIntegral $ minSize w priv height) + (fromIntegral surplus)*(nneg $ weight w)/wsum
|
||||
priv' = layout w priv wWidth height
|
||||
let wWidth = floor $ (fromIntegral $ minSize w priv height screen) + (fromIntegral surplus)*(nneg $ weight w)/wsum
|
||||
priv' = layout w priv wWidth height screen
|
||||
in WidgetState w wX y wWidth height priv'
|
||||
|
||||
nneg :: (Num a, Ord a) => a -> a
|
||||
|
@ -145,7 +145,7 @@ instance WidgetClass Separator where
|
|||
type WidgetData Separator = ()
|
||||
initWidget _ _ _ = return ()
|
||||
|
||||
minSize (Separator s _) _ _ = s
|
||||
minSize (Separator s _) _ _ _ = s
|
||||
weight (Separator _ w) = w
|
||||
render _ _ _ _ _ = return ()
|
||||
|
||||
|
|
|
@ -20,12 +20,12 @@ instance WidgetClass AlphaBox where
|
|||
type WidgetData AlphaBox = AlphaBoxState
|
||||
initWidget (AlphaBox _ widgets) phi disp = liftM AlphaBoxState $ mapM (createWidgetState phi disp) widgets
|
||||
|
||||
minSize (AlphaBox _ _) (AlphaBoxState widgetStates) height =
|
||||
sum (map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height) widgetStates)
|
||||
minSize (AlphaBox _ _) (AlphaBoxState widgetStates) height screen =
|
||||
sum (map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height screen) widgetStates)
|
||||
|
||||
weight (AlphaBox _ widgets) = sum (map (\(Widget w) -> weight w) widgets)
|
||||
|
||||
layout (AlphaBox _ _) (AlphaBoxState widgetStates) width height = AlphaBoxState $ layoutWidgets widgetStates 0 0 width height
|
||||
layout (AlphaBox _ _) (AlphaBoxState widgetStates) width height screen = AlphaBoxState $ layoutWidgets widgetStates 0 0 width height screen
|
||||
|
||||
render (AlphaBox alpha _) (AlphaBoxState widgetStates) w h screen = do
|
||||
renderWithSimilarSurface ContentColorAlpha w h $ \surface -> do
|
||||
|
|
|
@ -55,7 +55,7 @@ instance WidgetClass Clock where
|
|||
return $ ClockState time
|
||||
|
||||
|
||||
minSize (Clock config) _ _ = clockSize config
|
||||
minSize (Clock config) _ _ _ = clockSize config
|
||||
|
||||
render (Clock config) (ClockState time) w h _ = do
|
||||
time <- liftIO getZonedTime
|
||||
|
|
|
@ -24,7 +24,7 @@ import Phi.X11.Atoms
|
|||
|
||||
data SystrayIconState = SystrayIconState deriving Show
|
||||
|
||||
data SystrayState = SystrayState [SystrayIconState] deriving Show
|
||||
data SystrayState = SystrayState Rectangle [SystrayIconState] deriving Show
|
||||
|
||||
data Systray = Systray deriving Show
|
||||
|
||||
|
@ -35,13 +35,18 @@ instance WidgetClass Systray where
|
|||
initWidget (Systray) phi dispvar = do
|
||||
forkIO $ systrayRunner phi dispvar
|
||||
|
||||
return $ SystrayState []
|
||||
return $ SystrayState (head . getScreens $ dispvar) []
|
||||
|
||||
minSize _ (SystrayState systrayScreen icons) height screen = case True of
|
||||
_ | screen == systrayScreen -> (length icons)*height
|
||||
| otherwise -> 0
|
||||
|
||||
minSize _ (SystrayState icons) height = (length icons)*height
|
||||
weight _ = 0
|
||||
|
||||
render Systray (SystrayState icons) w h screen = do
|
||||
return ()
|
||||
render Systray (SystrayState systrayScreen icons) w h screen = case True of
|
||||
_ | screen == systrayScreen -> do
|
||||
return ()
|
||||
| otherwise -> return ()
|
||||
|
||||
|
||||
systrayRunner :: Phi -> Display -> IO ()
|
||||
|
@ -117,21 +122,27 @@ handleEvent ClientMessageEvent { ev_message_type = message_type, ev_data = messa
|
|||
case messageData of
|
||||
(_:opcode:iconID:_) -> do
|
||||
case True of
|
||||
_ | opcode == sYSTEM_TRAY_REQUEST_DOCK -> do
|
||||
return ()
|
||||
_ | opcode == sYSTEM_TRAY_REQUEST_DOCK ->
|
||||
when (iconID /= 0) $ addIcon phi dispvar $ fromIntegral iconID
|
||||
|
||||
| opcode == sYSTEM_TRAY_BEGIN_MESSAGE || opcode == sYSTEM_TRAY_CANCEL_MESSAGE -> do
|
||||
| opcode == sYSTEM_TRAY_BEGIN_MESSAGE || opcode == sYSTEM_TRAY_CANCEL_MESSAGE ->
|
||||
return ()
|
||||
|
||||
| otherwise -> do
|
||||
putStrLn "Phi: unknown tray message"
|
||||
return ()
|
||||
|
||||
|
||||
_ ->
|
||||
return ()
|
||||
|
||||
|
||||
handleEvent _ _ _ _ = return ()
|
||||
|
||||
|
||||
addIcon :: Phi -> Display -> Window -> IO ()
|
||||
addIcon phi display window = do
|
||||
return ()
|
||||
|
||||
|
||||
systray :: Widget
|
||||
systray = Widget $ Systray
|
||||
|
|
|
@ -170,7 +170,7 @@ instance WidgetClass Taskbar where
|
|||
return $ TaskbarState 0 0 (-1) [] M.empty M.empty M.empty M.empty
|
||||
|
||||
|
||||
minSize _ _ _ = 0
|
||||
minSize _ _ _ _ = 0
|
||||
weight _ = 1
|
||||
|
||||
render (Taskbar config) TaskbarState { taskbarActiveWindow = activeWindow
|
||||
|
@ -182,21 +182,24 @@ instance WidgetClass Taskbar where
|
|||
, taskbarWindowScaledIcons = windowScaledIcons
|
||||
, taskbarWindowScreens = windowScreens
|
||||
} w h screen = do
|
||||
let screenWindows = filter ((== Just screen) . flip M.lookup windowScreens) windows
|
||||
let screenWindows = filter ((== Just screen) . flip M.lookup windowScreens) windows
|
||||
desktopNumbers = take desktopCount [0..]
|
||||
desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers
|
||||
windowCount = sum $ map (length . snd) $ desktops
|
||||
dstyle d = fmap (if d == currentDesktop then snd else fst) $ desktopStyle config
|
||||
dlabelwidth d = fromMaybe 0 $ fmap desktopLabelWidth $ dstyle d
|
||||
gap d ds = if null (snd $ desktops !! d) then 0 else desktopLabelGap ds
|
||||
dleftwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
|
||||
-> (borderLeft $ margin border) + (borderWidth border) + (borderLeft $ padding border)
|
||||
+ dlabelwidth d + gap d ds) $ dstyle d
|
||||
dwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
|
||||
-> (borderH $ margin border) + 2*(borderWidth border) + (borderH $ padding border)
|
||||
+ dlabelwidth d + gap d ds) $ dstyle d
|
||||
desktopsWidth = sum $ map dwidth desktopNumbers
|
||||
windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount)
|
||||
desktops = map (\desktop -> (desktop, filter (fromMaybe False . fmap (windowOnDesktop desktop) . flip M.lookup windowStates) screenWindows)) desktopNumbers
|
||||
|
||||
windowCount = sum $ map (length . snd) $ desktops
|
||||
|
||||
dstyle d = fmap (if d == currentDesktop then snd else fst) $ desktopStyle config
|
||||
dlabelwidth d = fromMaybe 0 $ fmap desktopLabelWidth $ dstyle d
|
||||
gap d ds = if null (snd $ desktops !! d) then 0 else desktopLabelGap ds
|
||||
dleftwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
|
||||
-> (borderLeft $ margin border) + (borderWidth border) + (borderLeft $ padding border)
|
||||
+ dlabelwidth d + gap d ds) $ dstyle d
|
||||
dwidth d = fromMaybe 0 $ fmap (\ds@DesktopStyle {desktopBorder = border}
|
||||
-> (borderH $ margin border) + 2*(borderWidth border) + (borderH $ padding border)
|
||||
+ dlabelwidth d + gap d ds) $ dstyle d
|
||||
|
||||
desktopsWidth = sum $ map dwidth desktopNumbers
|
||||
windowWidth = if windowCount == 0 then 0 else min (taskMaxSize config) ((w - desktopsWidth) `div` windowCount)
|
||||
|
||||
flip (flip foldM_ 0) desktops $ \nwindows (desktop, desktopWindows) -> do
|
||||
let dstyle' = dstyle desktop
|
||||
|
|
|
@ -162,7 +162,7 @@ updatePanels disp redraw = do
|
|||
area = panelArea panel
|
||||
|
||||
newPanel <- if not redraw then return panel else do
|
||||
let layoutedWidgets = withDimension area $ Widget.layoutWidgets (panelWidgetStates panel) 0 0
|
||||
let layoutedWidgets = (withDimension area $ Widget.layoutWidgets (panelWidgetStates panel) 0 0) $ panelScreenArea panel
|
||||
panel' = panel { panelWidgetStates = layoutedWidgets }
|
||||
|
||||
renderWith buffer $ do
|
||||
|
|
Reference in a new issue