module PopupF(popupShellF,popupShellF') where
import Command
import DShellF
import FDefaults
import Fudget
import FRequest
import Xcommand
import Geometry(Point(..), pP)
--import LayoutRequest(LayoutRequest)
import Loops(loopCompThroughRightF)
--import Message(Message(..))
--import Spops
import MapstateK
import Xtypes
--import NullF(putsK)
import CompSP
import Path(here)

popupShellF :: String -> Maybe Point -> F a b -> F a (a, b)
popupShellF = forall a b.
Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b)
popupShellF' forall a. Customiser a
standard

popupShellF' :: Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a,b)
popupShellF' :: forall a b.
Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b)
popupShellF' Customiser ShellF
pm String
title Maybe Point
optpos (F FSP a b
f) =
  let pos :: Point
pos = case Maybe Point
optpos of
              Just Point
pos -> Point
pos
              Maybe Point
Nothing -> Int -> Int -> Point
pP Int
300 Int
300
      params :: Customiser ShellF
params = Customiser ShellF
pm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall xxx. HasVisible xxx => Bool -> Customiser xxx
setVisible Bool
False forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Customiser ShellF
setDeleteQuit Bool
False
  in forall a b c d.
F (Either (Either a b) c) (Either (Either c d) a) -> F b d
loopCompThroughRightF (forall a b c d.
Customiser ShellF -> K a b -> F c d -> F (Either a c) (Either b d)
shellKF' Customiser ShellF
params (forall {b} {a}.
String
-> Point -> K (Either b a) (Either (Either a FRequest) (a, b))
popupK String
title Point
pos) 
			   (forall hi ho. FSP hi ho -> F hi ho
F{-ff-} forall a b. (a -> b) -> a -> b
$ forall {t1} {a} {t2} {b}.
(t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b
prepostMapSP forall {a} {b} {b}.
Message a (Either b b) -> Either (Message a b) b
pre forall {b} {b}.
Either (Message (Path, b) b) b -> Message (Path, b) b
post (forall {a1} {a2} {b}. SP a1 a2 -> SP (Either a1 b) (Either a2 b)
idRightSP FSP a b
f)))

pre :: Message a (Either b b) -> Either (Message a b) b
pre (Low a
m) = forall a b. a -> Either a b
Left (forall a b. a -> Message a b
Low a
m)
pre (High (Left b
a)) = forall a b. a -> Either a b
Left (forall a b. b -> Message a b
High b
a)
pre (High (Right b
a)) = forall a b. b -> Either a b
Right b
a
post :: Either (Message (Path, b) b) b -> Message (Path, b) b
post (Right b
a) = forall a b. a -> Message a b
Low (Path
here,b
a)
post (Left (Low (Path, b)
m)) = forall a b. a -> Message a b
Low (Path, b)
m
post (Left (High b
a)) = forall a b. b -> Message a b
High b
a

popupK :: String
-> Point -> K (Either b a) (Either (Either a FRequest) (a, b))
popupK String
title Point
pos =
  let kf :: (Bool, a)
-> Message a (Either b a)
-> ((Bool, a),
    [Message FRequest (Either (Either a FRequest) (a, b))])
kf s :: (Bool, a)
s@(Bool
mapped,a
trig) Message a (Either b a)
msg =
	  case Message a (Either b a)
msg of
	    High (Right a
trig') -> ((Bool
True,a
trig'), 
	      [forall a b. b -> Message a b
High (forall a b. a -> Either a b
Left (forall a b. a -> Either a b
Left a
trig')),forall {a} {a} {b}.
XCommand -> Message a (Either (Either a FRequest) b)
lowfromf (Bool -> XCommand
GrabEvents Bool
True)] forall a. [a] -> [a] -> [a]
++
	       if Bool -> Bool
not Bool
mapped then [forall a b. a -> Message a b
Low forall a b. (a -> b) -> a -> b
$ XCommand -> FRequest
XCmd XCommand
MapRaised] else [])
	    High (Left b
x) -> ((Bool
False,a
trig),
			      (if Bool
mapped then forall {b}. [Message FRequest b]
unmapcmds else []) forall a. [a] -> [a] -> [a]
++ 
			      [forall {a} {a} {b}.
XCommand -> Message a (Either (Either a FRequest) b)
lowfromf XCommand
UngrabEvents,forall a b. b -> Message a b
High (forall a b. b -> Either a b
Right (a
trig, b
x))])
	    Low a
_ -> ((Bool, a)
s, [])
      lowfromf :: XCommand -> Message a (Either (Either a FRequest) b)
lowfromf = forall a b. b -> Message a b
High forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. XCommand -> FRequest
XCmd
      unmapcmds :: [Message FRequest b]
unmapcmds = [forall a b. a -> Message a b
Low forall a b. (a -> b) -> a -> b
$ XCommand -> FRequest
XCmd XCommand
UnmapWindow,forall a b. a -> Message a b
Low forall a b. (a -> b) -> a -> b
$ XCommand -> FRequest
XCmd XCommand
Flush]
      startcmds :: [XCommand]
startcmds =
	  [String -> XCommand
StoreName String
title, Point -> XCommand
SetNormalHints Point
pos, Point -> XCommand
moveWindow Point
pos,
	   [WindowAttributes] -> XCommand
ChangeWindowAttributes [Bool -> WindowAttributes
CWSaveUnder Bool
True]]
  in forall {i} {o}. [XCommand] -> K i o -> K i o
xcommandsK [XCommand]
startcmds forall a b. (a -> b) -> a -> b
$
     forall {t} {hi} {ho}.
(t -> KEvent hi -> (t, [KCommand ho])) -> t -> K hi ho
mapstateK forall {a} {a} {b}.
(Bool, a)
-> Message a (Either b a)
-> ((Bool, a),
    [Message FRequest (Either (Either a FRequest) (a, b))])
kf (Bool
False,forall a. HasCallStack => String -> a
error String
"premature output from fudget inside popupShellF")