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

49 lines
1.4 KiB
Haskell

{-# 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