Added clock widget

This commit is contained in:
Matthias Schiffer 2011-07-14 20:21:30 +02:00
parent 7c0f602343
commit 861fa81d85
8 changed files with 184 additions and 74 deletions

View file

@ -10,6 +10,8 @@ module Phi.Border ( BorderWidth(..)
import Phi.Types import Phi.Types
import Phi.Widget import Phi.Widget
import Control.Monad
import Graphics.Rendering.Cairo import Graphics.Rendering.Cairo
@ -52,7 +54,7 @@ data Border = Border BorderConfig [Widget] deriving Show
instance WidgetClass Border where instance WidgetClass Border where
type WidgetData Border = BorderState type WidgetData Border = BorderState
initialState (Border _ widgets) = BorderState $ map createWidgetState widgets initWidget (Border _ widgets) phi disp = liftM BorderState $ mapM (createWidgetState phi disp) widgets
minSize (Border config widgets) = sum (map (\(Widget w) -> minSize w) widgets) + borderH p + 2*bw + borderH m minSize (Border config widgets) = sum (map (\(Widget w) -> minSize w) widgets) + borderH p + 2*bw + borderH m
where where
@ -74,7 +76,6 @@ instance WidgetClass Border where
height' = height - borderV m - 2*bw - borderV p height' = height - borderV m - 2*bw - borderV p
render (Border config _) (BorderState widgetStates) w h = do render (Border config _) (BorderState widgetStates) w h = do
save
newPath newPath
arc (x + width - radius) (y + radius) radius (-pi/2) 0 arc (x + width - radius) (y + radius) radius (-pi/2) 0
arc (x + width - radius) (y + height - radius) radius 0 (pi/2) arc (x + width - radius) (y + height - radius) radius 0 (pi/2)
@ -82,14 +83,16 @@ instance WidgetClass Border where
arc (x + radius) (y + radius) radius pi (pi*3/2) arc (x + radius) (y + radius) radius pi (pi*3/2)
closePath closePath
save
setSourceRGBA fr fg fb fa setSourceRGBA fr fg fb fa
fillPreserve fillPreserve
setSourceRGBA br bg bb ba setSourceRGBA br bg bb ba
setLineWidth $ fromIntegral bw setLineWidth $ fromIntegral bw
stroke strokePreserve
restore restore
clip
renderWidgets widgetStates renderWidgets widgetStates
where where
@ -105,6 +108,8 @@ instance WidgetClass Border where
(br, bg, bb, ba) = borderColor config (br, bg, bb, ba) = borderColor config
(fr, fg, fb, fa) = backgroundColor config (fr, fg, fb, fa) = backgroundColor config
handleMessage _ (BorderState widgetStates) m = BorderState $ handleMessageWidgets m widgetStates
border :: BorderConfig -> [Widget] -> Widget border :: BorderConfig -> [Widget] -> Widget

View file

@ -12,4 +12,3 @@ data PanelConfig = PanelConfig { panelPosition :: Position
defaultPanelConfig :: PanelConfig defaultPanelConfig :: PanelConfig
defaultPanelConfig = PanelConfig { panelPosition = Top, panelSize = 24 } defaultPanelConfig = PanelConfig { panelPosition = Top, panelSize = 24 }

View file

@ -1,13 +1,11 @@
{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE ExistentialQuantification, DeriveDataTypeable, StandaloneDeriving #-}
module Phi.Phi ( Phi module Phi.Phi ( Phi
, MessageBus
, Message , Message
, DefaultMessage(..)
, fromMessage , fromMessage
, initPhi , initPhi
, runPhi
, sendMessage , sendMessage
, getMessageBus
, receiveMessage , receiveMessage
) where ) where
@ -16,9 +14,11 @@ import Control.Monad
import Data.Typeable import Data.Typeable
data Phi = Phi (Chan Message) data Phi = Phi (Chan Message)
data MessageBus = MessageBus (Chan Message)
data Message = forall a. (Typeable a, Show a) => Message a data Message = forall a. (Typeable a, Show a) => Message a
deriving instance Show Message
data DefaultMessage = Repaint deriving (Typeable, Show)
fromMessage :: (Typeable a, Show a) => Message -> Maybe a fromMessage :: (Typeable a, Show a) => Message -> Maybe a
fromMessage (Message m) = cast m fromMessage (Message m) = cast m
@ -26,14 +26,8 @@ fromMessage (Message m) = cast m
initPhi :: IO Phi initPhi :: IO Phi
initPhi = liftM Phi newChan initPhi = liftM Phi newChan
runPhi :: Phi -> IO ()
runPhi (Phi chan) = forever $ readChan chan
sendMessage :: (Typeable a, Show a) => Phi -> a -> IO () sendMessage :: (Typeable a, Show a) => Phi -> a -> IO ()
sendMessage (Phi chan) = writeChan chan . Message sendMessage (Phi chan) = writeChan chan . Message
getMessageBus :: Phi -> IO MessageBus receiveMessage :: Phi -> IO Message
getMessageBus (Phi chan) = liftM MessageBus $ dupChan chan receiveMessage (Phi chan) = readChan chan
receiveMessage :: MessageBus -> IO Message
receiveMessage (MessageBus chan) = readChan chan

View file

@ -1,26 +1,35 @@
{-# LANGUAGE ExistentialQuantification, TypeFamilies, StandaloneDeriving, FlexibleContexts #-} {-# LANGUAGE ExistentialQuantification, TypeFamilies, StandaloneDeriving, FlexibleContexts #-}
module Phi.Widget ( Widget(..) module Phi.Widget ( Display
, Widget(..)
, WidgetClass(..) , WidgetClass(..)
, WidgetState(..) , WidgetState(..)
, separator , separator
, createWidgetState , createWidgetState
, layoutWidgets , layoutWidgets
, renderWidgets , renderWidgets
, handleMessageWidgets
) where ) where
import Control.Concurrent
import Control.Monad import Control.Monad
import Data.Traversable import Data.Traversable
import qualified Graphics.X11.Xlib
import Graphics.Rendering.Cairo import Graphics.Rendering.Cairo
import Phi.Phi import Phi.Phi
type Display = MVar Graphics.X11.Xlib.Display
class Show a => WidgetClass a where class Show a => WidgetClass a where
type WidgetData a :: * type WidgetData a :: *
initialState :: a -> WidgetData a initWidget :: a -> Phi -> Display -> IO (WidgetData a)
minSize :: a -> Int minSize :: a -> Int
@ -47,14 +56,16 @@ data WidgetState = forall a. (WidgetClass a, Show (WidgetData a)) => WidgetState
} }
deriving instance Show WidgetState deriving instance Show WidgetState
createWidgetState :: Widget -> WidgetState createWidgetState :: Phi -> Display -> Widget -> IO WidgetState
createWidgetState (Widget w) = WidgetState { stateWidget = w createWidgetState phi disp (Widget w) = do
, stateX = 0 priv <- initWidget w phi disp
, stateY = 0 return WidgetState { stateWidget = w
, stateWidth = 0 , stateX = 0
, stateHeight = 0 , stateY = 0
, statePrivateData = initialState w , stateWidth = 0
} , stateHeight = 0
, statePrivateData = priv
}
layoutWidgets :: [WidgetState] -> Int -> Int -> Int -> Int -> [WidgetState] layoutWidgets :: [WidgetState] -> Int -> Int -> Int -> Int -> [WidgetState]
layoutWidgets widgets x y width height = snd $ mapAccumL layoutWidgetAndX x widgets layoutWidgets widgets x y width height = snd $ mapAccumL layoutWidgetAndX x widgets
@ -98,7 +109,7 @@ data Separator = Separator Int Float deriving Show
instance WidgetClass Separator where instance WidgetClass Separator where
type WidgetData Separator = () type WidgetData Separator = ()
initialState _ = () initWidget _ _ _ = return ()
minSize (Separator s _) = s minSize (Separator s _) = s
weight (Separator _ w) = w weight (Separator _ w) = w

78
lib/Phi/Widgets/Clock.hs Normal file
View file

@ -0,0 +1,78 @@
{-# LANGUAGE DeriveDataTypeable, TypeFamilies #-}
module Phi.Widgets.Clock ( ClockConfig(..)
, defaultClockConfig
, clock
) where
import Control.Concurrent
import Control.Monad
import Data.Typeable
import Data.Time.LocalTime
import Data.Time.Format
import Graphics.Rendering.Cairo
import Graphics.Rendering.Pango.Cairo
import Graphics.Rendering.Pango.Enums (PangoRectangle(..))
import Graphics.Rendering.Pango.Layout
import System.Locale
import Phi.Phi
import Phi.Types
import Phi.Widget
data ClockConfig = ClockConfig { clockFormat :: !String
, fontColor :: !Color
, lineSpacing :: !Double
, clockSize :: !Int
} deriving Show
defaultClockConfig :: ClockConfig
defaultClockConfig = ClockConfig "%R" (0, 0, 0, 1) 0 50
data Clock = Clock ClockConfig deriving Show
instance WidgetClass Clock where
type WidgetData Clock = ()
initWidget (Clock _) phi _ = do
forkIO $ forever $ do
time <- getZonedTime
sendMessage phi Repaint
threadDelay $ ceiling $ 1000000*(max 1 $ 60 - (todSec . localTimeOfDay . zonedTimeToLocalTime $ time))
return ()
minSize (Clock config ) = clockSize config
render (Clock config) _ w h = do
time <- liftIO getZonedTime
let (r, g, b, a) = fontColor config
str = formatTime defaultTimeLocale (clockFormat config) time
setSourceRGBA r g b a
layout <- createLayout ""
(_, PangoRectangle _ _ textWidth textHeight) <- liftIO $ do
layoutSetMarkup layout str
layoutSetAlignment layout AlignCenter
layoutSetSpacing layout $ lineSpacing config
layoutGetExtents layout
let scalef = min 1 ((fromIntegral w)/textWidth)
when (scalef < 1) $ do
scale scalef scalef
updateLayout layout
(_, PangoRectangle _ _ textWidth' textHeight') <- liftIO $ layoutGetExtents layout
moveTo (((fromIntegral w)/scalef - textWidth')/2) (((fromIntegral h)/scalef - textHeight')/2)
showLayout layout
clock :: ClockConfig -> Widget
clock config = do
Widget $ Clock config

View file

@ -1,8 +1,8 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, PatternGuards #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Phi.X11 ( XConfig(..) module Phi.X11 ( XConfig(..)
, defaultXConfig , defaultXConfig
, initPhiX , runPhi
) where ) where
import Graphics.X11.Xlib import Graphics.X11.Xlib
@ -31,25 +31,26 @@ import qualified Phi.Widget as Widget
import Phi.X11.Atoms import Phi.X11.Atoms
import qualified Phi.Bindings.Util as Util import qualified Phi.Bindings.Util as Util
data XConfig = XConfig { phiXScreenInfo :: Display -> IO [Rectangle] data XConfig = XConfig { phiXScreenInfo :: !(Display -> IO [Rectangle])
} }
data PhiState = PhiState { phiRootPixmap :: Pixmap data PhiState = PhiState { phiPhi :: !Phi
, phiPanels :: [PanelState] , phiRootPixmap :: !Pixmap
, phiPanels :: ![PanelState]
} }
data PanelState = PanelState { panelWindow :: Window data PanelState = PanelState { panelWindow :: !Window
, panelGC :: GC , panelGC :: !GC
, panelPixmap :: Pixmap , panelPixmap :: !Pixmap
, panelSurface :: Surface , panelSurface :: !Surface
, panelArea :: Rectangle , panelArea :: !Rectangle
, panelScreenArea :: Rectangle , panelScreenArea :: !Rectangle
, panelWidgetStates :: [Widget.WidgetState] , panelWidgetStates :: ![Widget.WidgetState]
} }
data PhiConfig = PhiConfig { phiPanelConfig :: Panel.PanelConfig data PhiConfig = PhiConfig { phiPanelConfig :: !Panel.PanelConfig
, phiXConfig :: XConfig , phiXConfig :: !XConfig
, phiAtoms :: Atoms , phiAtoms :: !Atoms
} }
newtype PhiReader a = PhiReader (ReaderT PhiConfig IO a) newtype PhiReader a = PhiReader (ReaderT PhiConfig IO a)
@ -64,12 +65,6 @@ newtype PhiX a = PhiX (StateT PhiState PhiReader a)
runPhiX :: PhiConfig -> PhiState -> PhiX a -> IO (a, PhiState) runPhiX :: PhiConfig -> PhiState -> PhiX a -> IO (a, PhiState)
runPhiX config st (PhiX a) = runPhiReader config $ runStateT a st runPhiX config st (PhiX a) = runPhiReader config $ runStateT a st
forkPhiX :: PhiX () -> PhiX ThreadId
forkPhiX f = do
config <- ask
state <- get
liftIO $ forkIO $ (runPhiX config state f >> return ())
withMVarX :: MVar a -> (a -> PhiX b) -> PhiX b withMVarX :: MVar a -> (a -> PhiX b) -> PhiX b
withMVarX m f = do withMVarX m f = do
a <- liftIO $ takeMVar m a <- liftIO $ takeMVar m
@ -81,18 +76,23 @@ defaultXConfig = XConfig { phiXScreenInfo = getScreenInfo
} }
initPhiX :: Phi -> XConfig -> Panel.PanelConfig -> [Widget.Widget] -> IO () runPhi :: XConfig -> Panel.PanelConfig -> [Widget.Widget] -> IO ()
initPhiX phi xconfig config widgets = do runPhi xconfig config widgets = do
phi <- initPhi
disp <- openDisplay [] disp <- openDisplay []
atoms <- initAtoms disp atoms <- initAtoms disp
selectInput disp (defaultRootWindow disp) $ propertyChangeMask.|.structureNotifyMask selectInput disp (defaultRootWindow disp) $ propertyChangeMask.|.structureNotifyMask
runPhiX PhiConfig { phiXConfig = xconfig, phiPanelConfig = config, phiAtoms = atoms } PhiState { phiRootPixmap = 0, phiPanels = [] } $ do runPhiX PhiConfig { phiXConfig = xconfig, phiPanelConfig = config, phiAtoms = atoms } PhiState { phiPhi = phi, phiRootPixmap = 0, phiPanels = [] } $ do
updateRootPixmap disp updateRootPixmap disp
screens <- liftIO $ phiXScreenInfo xconfig disp screens <- liftIO $ phiXScreenInfo xconfig disp
panels <- mapM (createPanel disp widgets) screens
dispvar <- liftIO $ newEmptyMVar
widgetStates <- liftIO $ mapM (Widget.createWidgetState phi dispvar) widgets
panels <- mapM (createPanel disp widgetStates) screens
forM_ panels $ \panel -> do forM_ panels $ \panel -> do
setPanelProperties disp panel setPanelProperties disp panel
liftIO $ mapWindow disp (panelWindow panel) liftIO $ mapWindow disp (panelWindow panel)
@ -101,23 +101,36 @@ initPhiX phi xconfig config widgets = do
updatePanels disp True updatePanels disp True
dispvar <- liftIO $ newMVar disp liftIO $ putMVar dispvar disp
liftIO $ forkIO $ receiveEvents phi dispvar liftIO $ forkIO $ receiveEvents phi dispvar
messagebus <- liftIO $ getMessageBus phi forever $ do
forkPhiX $ forever $ do message <- liftIO $ receiveMessage phi
message <- liftIO $ receiveMessage messagebus
handleMessage dispvar message handleMessage dispvar message
return () return ()
handlePanel :: Message -> PanelState -> PanelState
handlePanel message panel@PanelState {panelWidgetStates = widgets} = panel {panelWidgetStates = widgets'}
where
widgets' = Widget.handleMessageWidgets message widgets
handleMessage :: MVar Display -> Message -> PhiX () handleMessage :: MVar Display -> Message -> PhiX ()
handleMessage dispvar m handleMessage dispvar m = do
| Just ExposeEvent {} <- fromMessage m = withMVarX dispvar $ \disp -> do modify $ \state@PhiState {phiPanels = panels} -> state {phiPanels = map (handlePanel m) panels}
updatePanels disp False
| Just event@PropertyEvent {} <- fromMessage m = withMVarX dispvar $ \disp -> do case (fromMessage m) of
handlePropertyUpdate disp event Just Repaint -> withMVarX dispvar $ \disp ->
handleMessage _ _ = return () updatePanels disp True
_ ->
case (fromMessage m) of
Just ExposeEvent {} -> withMVarX dispvar $ \disp ->
updatePanels disp False
Just event@PropertyEvent {} -> withMVarX dispvar $ \disp ->
handlePropertyUpdate disp event
_ ->
return ()
receiveEvents :: Phi -> MVar Display -> IO () receiveEvents :: Phi -> MVar Display -> IO ()
receiveEvents phi dispvar = do receiveEvents phi dispvar = do
@ -186,8 +199,9 @@ updateRootPixmap disp = do
modify $ \state -> state { phiRootPixmap = pixmap } modify $ \state -> state { phiRootPixmap = pixmap }
createPanel :: Display -> [Widget.Widget] -> Rectangle -> PhiX PanelState createPanel :: Display -> [Widget.WidgetState] -> Rectangle -> PhiX PanelState
createPanel disp widgets screenRect = do createPanel disp widgets screenRect = do
phi <- gets phiPhi
config <- asks phiPanelConfig config <- asks phiPanelConfig
let rect = panelBounds config screenRect let rect = panelBounds config screenRect
@ -201,7 +215,14 @@ createPanel disp widgets screenRect = do
pixmap <- liftIO $ withDimension rect (createPixmap disp win) depth pixmap <- liftIO $ withDimension rect (createPixmap disp win) depth
surface <- liftIO $ withDimension rect $ Util.createXlibSurface disp pixmap visual surface <- liftIO $ withDimension rect $ Util.createXlibSurface disp pixmap visual
return PanelState { panelWindow = win, panelGC = gc, panelPixmap = pixmap, panelSurface = surface, panelArea = rect, panelScreenArea = screenRect, panelWidgetStates = map Widget.createWidgetState widgets } return PanelState { panelWindow = win
, panelGC = gc
, panelPixmap = pixmap
, panelSurface = surface
, panelArea = rect
, panelScreenArea = screenRect
, panelWidgetStates = widgets
}
createPanelWindow :: Display -> Rectangle -> PhiX Window createPanelWindow :: Display -> Rectangle -> PhiX Window
createPanelWindow disp rect = do createPanelWindow disp rect = do

View file

@ -11,8 +11,9 @@ maintainer: mschiffer@universe-factory.net
build-type: Simple build-type: Simple
library library
build-depends: base >= 4, template-haskell, mtl, cairo, X11 build-depends: base >= 4, template-haskell, mtl, time, old-locale, X11, cairo, pango
exposed-modules: Phi.Types, Phi.Phi, Phi.Panel, Phi.Widget, Phi.Border, Phi.X11 exposed-modules: Phi.Types, Phi.Phi, Phi.Panel, Phi.Widget, Phi.Border, Phi.X11,
Phi.Widgets.Clock
other-modules: Phi.X11.Atoms, Phi.X11.AtomList, Phi.Bindings.Util other-modules: Phi.X11.Atoms, Phi.X11.AtomList, Phi.Bindings.Util
hs-source-dirs: lib hs-source-dirs: lib

View file

@ -1,19 +1,20 @@
import Phi.Phi
import Phi.Types import Phi.Types
import Phi.Widget import Phi.Widget
import Phi.Panel import Phi.Panel
import Phi.Border import Phi.Border
import Phi.X11 import Phi.X11
import Phi.Widgets.Clock
import Data.Monoid
main :: IO () main :: IO ()
main = do main = do
phi <- initPhi runPhi defaultXConfig defaultPanelConfig { panelPosition = Bottom }
initPhiX phi defaultXConfig defaultPanelConfig { panelPosition = Bottom } [border border1 [border border3 [], border border3 []], border border2 [], border brightBorder [theClock]]
[border border1 [border border3 [], border border3 []], border border2 []]
runPhi phi
where where
theClock = clock defaultClockConfig { clockFormat = "<span font='Sans 8'>%R</span>\n<span font='Sans 6'>%A %d %B</span>"
, lineSpacing = (-2)
, clockSize = 75
}
brightBorder = BorderConfig (simpleBorderWidth 1) 1 (BorderWidth (-2) 3 0 3) (0.5, 0.5, 0.5, 0.65) (0.85, 0.85, 0.85, 0.8) 5 0
border1 = BorderConfig (simpleBorderWidth 1) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.25, 0.25, 0.25, 0.5) 7 2 border1 = BorderConfig (simpleBorderWidth 1) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.25, 0.25, 0.25, 0.5) 7 2
border2 = BorderConfig (simpleBorderWidth 1) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.5, 0.0, 0.25, 0.5) 7 1 border2 = BorderConfig (simpleBorderWidth 1) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.5, 0.0, 0.25, 0.5) 7 1
border3 = BorderConfig (simpleBorderWidth 0) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.0, 0.0, 0.5, 0.5) 3 1 border3 = BorderConfig (simpleBorderWidth 0) 1 (simpleBorderWidth 2) (1, 1, 1, 0.5) (0.0, 0.0, 0.5, 0.5) 3 1