2011-08-21 08:40:08 +02:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses, StandaloneDeriving, ExistentialQuantification, FlexibleInstances #-}
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 08:40:08 +02:00
|
|
|
module Phi.Widgets.AlphaBox ( AlphaBox
|
|
|
|
, alphaBox
|
2011-07-18 18:06:00 +02:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Phi.Types
|
|
|
|
import Phi.Widget
|
|
|
|
|
|
|
|
import Control.Monad
|
|
|
|
|
|
|
|
import Graphics.Rendering.Cairo
|
|
|
|
|
|
|
|
|
2011-08-21 19:34:16 +02:00
|
|
|
data AlphaBox w s c = (Widget w s c) => AlphaBox !Double !w
|
|
|
|
deriving instance Show (AlphaBox w s c)
|
|
|
|
deriving instance Eq (AlphaBox w s c)
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 19:34:16 +02:00
|
|
|
instance Eq s => Widget (AlphaBox w s c) s () where
|
2011-08-21 08:40:08 +02:00
|
|
|
initWidget (AlphaBox _ w) = initWidget w
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 08:40:08 +02:00
|
|
|
minSize (AlphaBox _ w) = minSize w
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 08:40:08 +02:00
|
|
|
weight (AlphaBox _ w) = weight w
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 08:40:08 +02:00
|
|
|
layout (AlphaBox _ w) = layout w
|
2011-07-18 18:06:00 +02:00
|
|
|
|
2011-08-21 19:34:16 +02:00
|
|
|
render (AlphaBox alpha w) s x y width height screen = do
|
|
|
|
surfaces <- render w s x y width height screen
|
|
|
|
let surfacesWidths = zipWith (\(updated, SurfaceSlice x surf) x' -> (updated, x, x'-x, surf)) surfaces (map (\(_, SurfaceSlice x _) -> x) (tail surfaces) ++ [width])
|
|
|
|
forM surfacesWidths $ \(updated, x, surfWidth, surf) -> do
|
|
|
|
surf' <- createImageSurface FormatARGB32 surfWidth height
|
|
|
|
renderWith surf' $ do
|
|
|
|
setOperator OperatorSource
|
|
|
|
withPatternForSurface surf setSource
|
|
|
|
paint
|
2011-07-18 18:06:00 +02:00
|
|
|
|
|
|
|
setOperator OperatorDestIn
|
|
|
|
setSourceRGBA 0 0 0 alpha
|
|
|
|
paint
|
|
|
|
|
2011-08-21 19:34:16 +02:00
|
|
|
return (updated, SurfaceSlice x surf')
|
2011-08-21 08:40:08 +02:00
|
|
|
|
|
|
|
handleMessage (AlphaBox _ w) = handleMessage w
|
2011-07-18 18:06:00 +02:00
|
|
|
|
|
|
|
|
2011-08-21 19:34:16 +02:00
|
|
|
alphaBox :: (Widget w s c) => Double -> w -> AlphaBox w s c
|
2011-08-21 08:40:08 +02:00
|
|
|
alphaBox = AlphaBox
|
2011-07-18 18:06:00 +02:00
|
|
|
|