This repository has been archived on 2025-03-02. You can view files and clone it, but cannot push or open issues or pull requests.
phi/lib/Phi/Widget.hs

147 lines
4.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ExistentialQuantification, StandaloneDeriving, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies #-}
2011-07-14 00:09:20 +02:00
2011-07-14 22:50:03 +02:00
module Phi.Widget ( Display(..)
, withDisplay
2011-07-15 09:17:57 +02:00
, getAtoms
2011-07-19 11:16:50 +02:00
, getScreenWindows
2011-07-16 15:55:31 +02:00
, getScreens
, unionArea
2011-07-14 20:21:30 +02:00
, Widget(..)
, CompoundWidget
, (<~>)
, Separator
2011-07-14 00:09:20 +02:00
, separator
) where
import Control.Arrow
import Control.Arrow.Transformer
import Control.CacheArrow
import Control.Concurrent.MVar
2011-07-14 00:09:20 +02:00
import Control.Monad
2011-07-15 09:17:57 +02:00
import Control.Monad.IO.Class
2011-07-14 20:21:30 +02:00
import Data.Traversable hiding (forM)
2011-07-14 00:09:20 +02:00
2011-07-16 15:55:31 +02:00
import qualified Graphics.X11.Xlib as Xlib
2011-07-14 00:09:20 +02:00
import Graphics.Rendering.Cairo
2011-07-14 06:16:04 +02:00
import Phi.Phi
2011-07-15 09:17:57 +02:00
import Phi.X11.Atoms
2011-07-14 06:16:04 +02:00
2011-07-14 00:09:20 +02:00
2011-08-12 03:18:46 +02:00
data Display = Display !(MVar Xlib.Display) !Atoms ![(Xlib.Rectangle, Xlib.Window)]
2011-07-14 22:50:03 +02:00
2011-07-16 15:55:31 +02:00
withDisplay :: MonadIO m => Display -> (Xlib.Display -> m a) -> m a
withDisplay (Display dispvar _ _) f = do
2011-07-15 09:17:57 +02:00
disp <- liftIO $ takeMVar dispvar
2011-07-14 22:50:03 +02:00
a <- f disp
2011-07-15 09:17:57 +02:00
liftIO $ putMVar dispvar disp
2011-07-14 22:50:03 +02:00
return a
2011-07-14 20:21:30 +02:00
2011-07-15 09:17:57 +02:00
getAtoms :: Display -> Atoms
2011-07-16 15:55:31 +02:00
getAtoms (Display _ atoms _) = atoms
2011-07-19 11:16:50 +02:00
getScreenWindows :: Display -> [(Xlib.Rectangle, Xlib.Window)]
getScreenWindows (Display _ _ screenWindows) = screenWindows
2011-07-16 15:55:31 +02:00
getScreens :: Display -> [Xlib.Rectangle]
2011-07-19 11:16:50 +02:00
getScreens = map fst . getScreenWindows
2011-07-16 15:55:31 +02:00
unionArea :: Xlib.Rectangle -> Xlib.Rectangle -> Int
unionArea a b = fromIntegral $ uw*uh
where
uw = max 0 $ (min ax2 bx2) - (max ax1 bx1)
uh = max 0 $ (min ay2 by2) - (max ay1 by1)
Xlib.Rectangle ax1 ay1 aw ah = a
Xlib.Rectangle bx1 by1 bw bh = b
ax2 = ax1 + fromIntegral aw
ay2 = ay1 + fromIntegral ah
bx2 = bx1 + fromIntegral bw
by2 = by1 + fromIntegral bh
2011-07-15 09:17:57 +02:00
2011-07-14 20:21:30 +02:00
class (Show a, Eq a, Eq d) => Widget a d | a -> d where
initWidget :: a -> Phi -> Display -> IO d
2011-07-14 00:09:20 +02:00
minSize :: a -> d -> Int -> Xlib.Rectangle -> Int
2011-07-14 00:09:20 +02:00
weight :: a -> Float
weight _ = 0
layout :: a -> d -> Int -> Int -> Xlib.Rectangle -> d
layout _ priv _ _ _ = priv
2011-07-14 00:09:20 +02:00
render :: a -> d -> Int -> Int -> Int -> Int -> Xlib.Rectangle -> Render ()
2011-07-14 06:16:04 +02:00
handleMessage :: a -> d -> Message -> d
2011-07-14 06:16:04 +02:00
handleMessage _ priv _ = priv
2011-07-14 00:09:20 +02:00
{-createStateRender :: Widget a d => CacheArrow (Kleisli IO) (a, d, Int, Int, Int, Int, Xlib.Rectangle) Surface
createStateRender = lift . Kleisli $ \(widget, state, x, y, w, h, screen) -> do
surface <- createImageSurface FormatARGB32 w h
renderWith surface $ do
setOperator OperatorClear
paint
setOperator OperatorOver
render widget state x y w h screen
return surface-}
data CompoundWidget a da b db = (Widget a da, Widget b db) => CompoundWidget !a !b
deriving instance Eq (CompoundWidget a da b db)
deriving instance Show (CompoundWidget a da b db)
data CompoundState a da b db = (Widget a da, Widget b db) => CompoundState !da !db !Int
deriving instance Eq (CompoundState a da b db)
instance Widget (CompoundWidget a da b db) (CompoundState a da b db) where
initWidget (CompoundWidget a b) phi disp = liftM3 CompoundState (initWidget a phi disp) (initWidget b phi disp) (return 0)
minSize (CompoundWidget a b) (CompoundState da db _) height screen = minSize a da height screen + minSize b db height screen
weight (CompoundWidget a b) = weight' a + weight' b
layout c@(CompoundWidget a b) d@(CompoundState da db _) width height screen = CompoundState da' db' xb
where
sizesum = minSize c d height screen
wsum = let wsum = weight c
2011-07-14 01:47:10 +02:00
in if wsum > 0 then wsum else 1
surplus = width - sizesum
(xb, da') = layoutWidget a da
(_, db') = layoutWidget b db
layoutWidget w priv = let wWidth = floor $ (fromIntegral $ minSize w priv height screen) + (fromIntegral surplus)*(weight' w)/wsum
in (wWidth, layout w priv wWidth height screen)
render (CompoundWidget a b) (CompoundState da db xb) x y w h screen = do
save
render a da x y xb h screen
restore
translate (fromIntegral xb) 0
render b db (x+xb) y (w-xb) h screen
2011-07-14 01:47:10 +02:00
handleMessage (CompoundWidget a b) (CompoundState da db xb) message = CompoundState (handleMessage a da message) (handleMessage b db message) xb
2011-07-14 00:09:20 +02:00
weight' :: (Widget a da) => a -> Float
weight' = max 0 . weight
2011-07-14 00:09:20 +02:00
(<~>) :: (Widget a da, Widget b db) => a -> b -> CompoundWidget a da b db
a <~> b = CompoundWidget a b
2011-07-14 00:09:20 +02:00
data Separator = Separator !Int !Float deriving (Show, Eq)
2011-07-14 00:09:20 +02:00
instance Widget Separator () where
2011-07-14 20:21:30 +02:00
initWidget _ _ _ = return ()
2011-07-14 00:09:20 +02:00
minSize (Separator s _) _ _ _ = s
2011-07-14 00:09:20 +02:00
weight (Separator _ w) = w
render _ _ _ _ _ _ _ = return ()
2011-07-14 00:09:20 +02:00
separator :: Int -> Float -> Separator
separator = Separator