module Expose where
import Message
import Cont
import Fudget
import Geometry(Rect,rmax)
import FRequest
import Event
collectExposeK :: Bool -> Rect -> Int -> ([Rect] -> K a b) -> K a b
collectExposeK :: forall a b. Bool -> Rect -> Int -> ([Rect] -> K a b) -> K a b
collectExposeK Bool
grX Rect
r Int
aft [Rect] -> K a b
c = [Rect] -> Int -> K a b
collect [Rect
r] Int
aft
where collect :: [Rect] -> Int -> K a b
collect [Rect]
rs Int
aft =
if Int
aft forall a. Eq a => a -> a -> Bool
== Int
0 then [Rect] -> K a b
c [Rect]
rs
else forall {hi} {a} {ho}. (KEvent hi -> Maybe a) -> Cont (K hi ho) a
waitForK (\KEvent a
r ->
case KEvent a
r of
Low (XEvt (Expose Rect
r Int
aft')) | Bool -> Bool
not Bool
grX -> forall a. a -> Maybe a
Just (Rect
r,Int
aft')
Low (XEvt (GraphicsExpose Rect
r Int
aft' Int
_ Int
_)) | Bool
grX -> forall a. a -> Maybe a
Just (Rect
r,Int
aft')
KEvent a
_ -> forall a. Maybe a
Nothing) forall a b. (a -> b) -> a -> b
$ \(Rect
r,Int
aft')->
[Rect] -> Int -> K a b
collect (Rect
rforall a. a -> [a] -> [a]
:[Rect]
rs) Int
aft'
maxExposeK :: Bool -> Rect -> Int -> (Rect -> K a b) -> K a b
maxExposeK Bool
grX Rect
r Int
aft Rect -> K a b
c = forall a b. Bool -> Rect -> Int -> ([Rect] -> K a b) -> K a b
collectExposeK Bool
grX Rect
r Int
aft forall a b. (a -> b) -> a -> b
$ \[Rect]
rs ->
Rect -> K a b
c (forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Rect -> Rect -> Rect
rmax [Rect]
rs)