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/Border.hs

139 lines
4.8 KiB
Haskell
Raw Normal View History

2011-07-14 00:09:20 +02:00
{-# LANGUAGE TypeFamilies #-}
2011-07-13 02:13:01 +02:00
module Phi.Border ( BorderWidth(..)
, simpleBorderWidth
2011-07-15 15:31:46 +02:00
, borderH
, borderV
, BorderConfig(..)
, defaultBorderConfig
2011-07-15 09:17:57 +02:00
, drawBorder
, roundRectangle
2011-07-13 02:13:01 +02:00
, border
) where
2011-07-14 00:09:20 +02:00
import Phi.Types
import Phi.Widget
2011-07-13 02:13:01 +02:00
2011-07-14 20:21:30 +02:00
import Control.Monad
2011-07-13 02:13:01 +02:00
import Graphics.Rendering.Cairo
data BorderWidth = BorderWidth { borderTop :: !Int
, borderRight :: !Int
, borderBottom :: !Int
, borderLeft :: !Int
2011-07-14 01:47:10 +02:00
} deriving Show
2011-07-13 02:13:01 +02:00
simpleBorderWidth :: Int -> BorderWidth
simpleBorderWidth w = BorderWidth w w w w
borderH :: BorderWidth -> Int
borderH bw = borderLeft bw + borderRight bw
borderV :: BorderWidth -> Int
borderV bw = borderTop bw + borderBottom bw
2011-08-12 03:18:46 +02:00
data BorderState = BorderState ![WidgetState] deriving Show
data BorderConfig = BorderConfig { margin :: !BorderWidth
, borderWidth :: !Int
, padding :: !BorderWidth
, borderColor :: !Color
, backgroundColor :: !Color
2011-07-17 19:20:19 +02:00
, cornerRadius :: !Int
, borderWeight :: !Float
} deriving Show
defaultBorderConfig = BorderConfig { margin = simpleBorderWidth 0
, borderWidth = 1
, padding = simpleBorderWidth 1
, borderColor = (0, 0, 0, 1)
, backgroundColor = (0, 0, 0, 0)
, cornerRadius = 0
, borderWeight = 1
}
2011-08-12 03:18:46 +02:00
data Border = Border !BorderConfig ![Widget] deriving Show
2011-07-13 02:13:01 +02:00
2011-07-14 00:09:20 +02:00
instance WidgetClass Border where
type WidgetData Border = BorderState
2011-07-14 20:21:30 +02:00
initWidget (Border _ widgets) phi disp = liftM BorderState $ mapM (createWidgetState phi disp) widgets
2011-07-14 00:09:20 +02:00
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)
2011-07-13 02:13:01 +02:00
where
childSize = sum $ map (\(WidgetState {stateWidget = w, statePrivateData = priv}) -> minSize w priv height' screen) widgetStates
m = margin config
bw = borderWidth config
p = padding config
2011-07-17 19:20:19 +02:00
cr = cornerRadius config
height' = height - borderV m - 2*bw - borderV p
2011-07-13 02:13:01 +02:00
weight (Border config _) = borderWeight config
2011-07-13 02:13:01 +02:00
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
p = padding config
x = borderLeft m + bw + borderLeft p
y = borderTop m + bw + borderTop p
width' = width - borderH m - 2*bw - borderH p
height' = height - borderV m - 2*bw - borderV p
render (Border config _) (BorderState widgetStates) w h screen = when (w > borderH m - 2*bw - borderH p) $ do
2011-07-15 09:17:57 +02:00
drawBorder config 0 0 w h
2011-07-14 20:21:30 +02:00
clip
2011-07-16 15:55:31 +02:00
renderWidgets widgetStates screen
where
m = margin config
bw = borderWidth config
p = padding config
2011-07-14 20:21:30 +02:00
handleMessage _ (BorderState widgetStates) m = BorderState $ handleMessageWidgets m widgetStates
2011-07-15 09:17:57 +02:00
drawBorder :: BorderConfig -> Int -> Int -> Int -> Int -> Render ()
drawBorder config dx dy w h = do
roundRectangle x y width height radius
save
setSourceRGBA fr fg fb fa
fillPreserve
setSourceRGBA br bg bb ba
setLineWidth $ fromIntegral bw
strokePreserve
restore
where
m = margin config
bw = borderWidth config
p = padding config
2011-07-17 19:20:19 +02:00
radius = fromIntegral $ cornerRadius config
2011-07-15 09:17:57 +02:00
x = (fromIntegral dx) + (fromIntegral $ borderLeft m) + (fromIntegral bw)/2
y = (fromIntegral dy) + (fromIntegral $ borderTop m) + (fromIntegral bw)/2
width = fromIntegral $ w - borderH m - bw
height = fromIntegral $ h - borderV m - bw
(br, bg, bb, ba) = borderColor config
(fr, fg, fb, fa) = backgroundColor config
roundRectangle :: Double -> Double -> Double -> Double -> Double -> Render ()
roundRectangle x y width height radius = do
newPath
arc (x + width - radius) (y + radius) radius (-pi/2) 0
arc (x + width - radius) (y + height - radius) radius 0 (pi/2)
arc (x + radius) (y + height - radius) radius (pi/2) pi
arc (x + radius) (y + radius) radius pi (pi*3/2)
closePath
2011-07-13 02:13:01 +02:00
border :: BorderConfig -> [Widget] -> Widget
2011-07-18 18:06:00 +02:00
border config = Widget . Border config