module UserLayoutF where
import Fudget
import FRequest
import Geometry(Rect)
import Spops(concatMapSP)
import CompSP(preMapSP,serCompSP)
import LayoutRequest
userLayoutF :: F a b -> F (Either (Path,Rect) a) (Either (Path,LayoutMessage) b)
userLayoutF :: forall a b.
F a b -> F (Either (Path, Rect) a) (Either (Path, LayoutMessage) b)
userLayoutF (F FSP a b
fud) = forall hi ho. FSP hi ho -> F hi ho
F (forall {t} {b}. (t -> [b]) -> SP t b
concatMapSP forall {a} {b}.
Message (a, FRequest) b
-> [Message (a, FRequest) (Either (a, LayoutMessage) b)]
post forall {a1} {b} {a2}. SP a1 b -> SP a2 a1 -> SP a2 b
`serCompSP` FSP a b
fud forall {a} {b} {t}. SP a b -> (t -> a) -> SP t b
`preMapSP` forall {a} {b}.
Message (a, FResponse) (Either (a, Rect) b)
-> Message (a, FResponse) b
pre)
where
pre :: Message (a, FResponse) (Either (a, Rect) b)
-> Message (a, FResponse) b
pre Message (a, FResponse) (Either (a, Rect) b)
msg =
case Message (a, FResponse) (Either (a, Rect) b)
msg of
High (Right b
x) -> forall a b. b -> Message a b
High b
x
High (Left (a
p,Rect
place)) -> forall a b. a -> Message a b
Low (a
p,LayoutResponse -> FResponse
LEvt (Rect -> LayoutResponse
LayoutPlace Rect
place))
Low (a, FResponse)
pev -> forall a b. a -> Message a b
Low (a, FResponse)
pev
post :: Message (a, FRequest) b
-> [Message (a, FRequest) (Either (a, LayoutMessage) b)]
post Message (a, FRequest) b
msg =
case Message (a, FRequest) b
msg of
High b
x -> [forall a b. b -> Message a b
High (forall a b. b -> Either a b
Right b
x)]
Low (a
p,LCmd LayoutMessage
req) -> [forall a b. b -> Message a b
High (forall a b. a -> Either a b
Left (a
p,LayoutMessage
req))]
Low (a, FRequest)
pcmd -> [forall a b. a -> Message a b
Low (a, FRequest)
pcmd]