summaryrefslogtreecommitdiffstats
path: root/lib/Phi/Widgets/AlphaBox.hs
blob: cd540e34bfd412858bf6646ba73dbcd4dd22c93c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
{-# LANGUAGE MultiParamTypeClasses, StandaloneDeriving, ExistentialQuantification, FlexibleInstances #-}

module Phi.Widgets.AlphaBox ( AlphaBox
                            , alphaBox
                            ) where

import Phi.Types
import Phi.Widget

import Control.Monad

import Graphics.Rendering.Cairo


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)

instance Eq s => Widget (AlphaBox w s c) s () where
  initWidget (AlphaBox _ w) = initWidget w
  
  minSize (AlphaBox _ w) = minSize w
  
  weight (AlphaBox _ w) = weight w
  
  layout (AlphaBox _ w) = layout w

  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
        
        setOperator OperatorDestIn
        setSourceRGBA 0 0 0 alpha
        paint
      
      return (updated, SurfaceSlice x surf')
  
  handleMessage (AlphaBox _ w) = handleMessage w


alphaBox :: (Widget w s c) => Double -> w -> AlphaBox w s c
alphaBox = AlphaBox