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/Widgets/AlphaBox.hs

53 lines
1.6 KiB
Haskell
Raw Permalink Normal View History

{-# LANGUAGE MultiParamTypeClasses, StandaloneDeriving, ExistentialQuantification, FlexibleInstances #-}
2011-07-18 18:06:00 +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
2011-08-21 21:39:26 +02:00
import Control.Monad.State.Strict
2011-07-18 18:06:00 +02:00
import Graphics.Rendering.Cairo
2011-09-08 19:15:23 +02:00
data AlphaBox w s c d = (Widget w s c d) => AlphaBox !Double !w
2011-07-18 18:06:00 +02:00
2011-09-08 19:15:23 +02:00
data AlphaBoxCache w s c d = (Widget w s c d) => AlphaBoxCache !c
2011-08-21 21:39:26 +02:00
2011-09-08 19:15:23 +02:00
instance (Eq s, Display d) => Widget (AlphaBox w s c d) s (AlphaBoxCache w s c d) d where
initWidget (AlphaBox _ w) = initWidget w
2011-08-21 21:39:26 +02:00
initCache (AlphaBox _ w) = AlphaBoxCache $ initCache w
2011-07-18 18:06:00 +02:00
minSize (AlphaBox _ w) = minSize w
2011-07-18 18:06:00 +02:00
weight (AlphaBox _ w) = weight w
2011-07-18 18:06:00 +02:00
render (AlphaBox alpha w) s x y width height screen = do
2011-08-21 21:39:26 +02:00
AlphaBoxCache c <- get
(surfaces, c') <- liftIO $ flip runStateT c $ render w s x y width height screen
put $ AlphaBoxCache c'
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
2011-08-21 21:39:26 +02:00
surf' <- liftIO $ 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
return (updated, SurfaceSlice x surf')
handleMessage (AlphaBox _ w) = handleMessage w
2011-07-18 18:06:00 +02:00
2011-09-08 19:15:23 +02:00
alphaBox :: (Widget w s c d) => Double -> w -> AlphaBox w s c d
alphaBox = AlphaBox
2011-07-18 18:06:00 +02:00