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

74 lines
1.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ExistentialQuantification #-}
2011-07-12 14:41:25 +02:00
module Phi.Panel ( Position(..)
2011-07-13 02:13:01 +02:00
, Color
2011-07-12 14:41:25 +02:00
, Panel(..)
, PanelClass(..)
, (<~>)
2011-07-12 16:47:24 +02:00
, PanelConfig(..)
, defaultPanelConfig
, separator
) where
import Data.Function
2011-07-12 16:47:24 +02:00
import Data.Monoid
2011-07-13 02:13:01 +02:00
import Graphics.Rendering.Cairo
2011-07-12 14:41:25 +02:00
data Position = Top | Bottom
2011-07-13 02:13:01 +02:00
type Color = (Double, Double, Double, Double)
class PanelClass a where
minSize :: a -> Int
weight :: a -> Float
weight _ = 0
2011-07-13 02:13:01 +02:00
render :: a -> Int -> Int -> Render ()
2011-07-12 16:47:24 +02:00
data Panel = forall a. PanelClass a => Panel a | CompoundPanel [Panel]
instance Monoid Panel where
mempty = CompoundPanel []
mappend a b = makePanel $ (toList a) ++ (toList b)
where
toList (Panel p) = [Panel p]
toList (CompoundPanel panels) = panels
makePanel [p] = p
makePanel panels = CompoundPanel panels
instance PanelClass Panel where
minSize (Panel p) = minSize p
2011-07-12 16:47:24 +02:00
minSize (CompoundPanel panels) = sum $ map minSize panels
weight (Panel p) = weight p
2011-07-12 16:47:24 +02:00
weight (CompoundPanel panels) = sum $ map weight panels
2011-07-13 02:13:01 +02:00
render (Panel p) w h = render p w h
render (CompoundPanel panels) _ _ = return ()
2011-07-12 16:47:24 +02:00
(<~>) :: Panel -> Panel -> Panel
(<~>) = mappend
2011-07-12 16:47:24 +02:00
data PanelConfig = PanelConfig { panelPosition :: Position
, panelSize :: Int
, panelContent :: Panel
}
2011-07-12 16:47:24 +02:00
defaultPanelConfig :: PanelConfig
defaultPanelConfig = PanelConfig { panelPosition = Top, panelSize = 24, panelContent = mempty }
data Separator = Separator Int Float
instance PanelClass Separator where
minSize (Separator s _) = s
weight (Separator _ w) = w
2011-07-13 02:13:01 +02:00
render (Separator _ _) _ _ = return ()
separator :: Int -> Float -> Panel
separator s w = Panel $ Separator s w