module Shells where

import FDefaults
import Fudget
import FRequest
import Xcommand
import DShellF
import EitherUtils
--import NullF
import CompOps
import Command
import FudgetIO
import Event
import Spops(concatMapSP)
import MapstateK

unmappedShellF :: t FRequest -> K a b -> F c d -> F (Either a c) (Either b d)
unmappedShellF t FRequest
cmds = forall {t :: * -> *} {a} {b} {c} {d}.
Foldable t =>
(ShellF -> ShellF)
-> t FRequest -> K a b -> F c d -> F (Either a c) (Either b d)
unmappedShellF' forall a. Customiser a
standard t FRequest
cmds

unmappedShellF' :: (ShellF -> ShellF)
-> t FRequest -> K a b -> F c d -> F (Either a c) (Either b d)
unmappedShellF' ShellF -> ShellF
pm t FRequest
cmds K a b
k =
    forall a b c d.
(ShellF -> ShellF) -> K a b -> F c d -> F (Either a c) (Either b d)
shellKF' (ShellF -> ShellF
pmforall b c a. (b -> c) -> (a -> b) -> a -> c
. forall xxx. HasVisible xxx => Bool -> Customiser xxx
setVisible Bool
Falseforall b c a. (b -> c) -> (a -> b) -> a -> c
. forall xxx. HasMargin xxx => Int -> Customiser xxx
setMargin Int
0)
	     (forall {t :: * -> *} {f :: * -> * -> *} {hi} {ho}.
(Foldable t, FudgetIO f) =>
t FRequest -> f hi ho -> f hi ho
putLows t FRequest
cmds K a b
k)
   
unmappedSimpleShellF :: String -> F i o -> F i o
unmappedSimpleShellF = forall i o. (ShellF -> ShellF) -> String -> F i o -> F i o
unmappedSimpleShellF' forall a. Customiser a
standard

unmappedSimpleShellF' :: Customiser ShellF -> String -> F i o -> F i o
unmappedSimpleShellF' :: forall i o. (ShellF -> ShellF) -> String -> F i o -> F i o
unmappedSimpleShellF' ShellF -> ShellF
pm String
name F i o
f = 
   forall {a}. Either a a -> a
stripEither forall a b e. (a -> b) -> F e a -> F e b
>^=< forall a b c d.
(ShellF -> ShellF) -> K a b -> F c d -> F (Either a c) (Either b d)
shellKF' ShellF -> ShellF
params forall {o}. K Bool o
k F i o
f  forall c d e. F c d -> SP e c -> F e d
>=^^< forall {b}. SP b (Either Bool b)
mapraiseSP where
     params :: ShellF -> ShellF
params = forall xxx. HasVisible xxx => Bool -> Customiser xxx
setVisible Bool
False forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShellF -> ShellF
pm
     startcmds :: [XCommand]
startcmds = [String -> XCommand
StoreName String
name]
     mapraiseSP :: SP b (Either Bool b)
mapraiseSP = forall {t} {b}. (t -> [b]) -> SP t b
concatMapSP ( \b
msg -> [forall a b. b -> Either a b
Right b
msg, forall a b. a -> Either a b
Left Bool
True])
     k :: K Bool o
k = forall {i} {o}. [XCommand] -> K i o -> K i o
xcommandsK [XCommand]
startcmds forall {o}. K Bool o
mapWindowK

mapWindowK :: K Bool ho
mapWindowK = forall {t} {hi} {ho}.
(t -> KEvent hi -> (t, [KCommand ho])) -> t -> K hi ho
mapstateK forall {b}.
Bool -> Message FResponse Bool -> (Bool, [Message FRequest b])
k1 Bool
False
  where
    k1 :: Bool -> Message FResponse Bool -> (Bool, [Message FRequest b])
k1 Bool
False  (High Bool
True)                  = (Bool
True,   [forall a b. a -> Message a b
Low forall a b. (a -> b) -> a -> b
$ XCommand -> FRequest
XCmd forall a b. (a -> b) -> a -> b
$ XCommand
MapRaised])
    k1 Bool
True   (High Bool
False)               = (Bool
False,  [forall a b. a -> Message a b
Low forall a b. (a -> b) -> a -> b
$ XCommand -> FRequest
XCmd forall a b. (a -> b) -> a -> b
$ XCommand
UnmapWindow])
    k1 Bool
_      (Low (XEvt (UnmapNotify Window
_))) = (Bool
False,  [])
    k1 Bool
_      (Low (XEvt (MapNotify Window
_)))   = (Bool
True,   [])
    k1 Bool
mapped Message FResponse Bool
_                            = (Bool
mapped, [])

-- Retained for backwards compatibility:
simpleShellF :: String -> [WindowAttributes] -> F c d -> F c d
simpleShellF String
name [WindowAttributes]
wattrs = forall i o. (ShellF -> ShellF) -> String -> F i o -> F i o
shellF' (forall xxx. HasWinAttr xxx => [WindowAttributes] -> Customiser xxx
setWinAttr [WindowAttributes]
wattrs) String
name