module ToggleButtonF(toggleF, oldToggleButtonF, oldToggleButtonF') where
import Spacer(marginF)
import CompOps((>=^<), (>^=<),(>+<),(>=^^<))
import CompSP(idRightSP)
import SpEither(filterRightSP)
import Spacers(compS,vCenterS,noStretchS)
import Placer(hBoxF,spacer1F)
import EitherUtils(stripEither)
import OnOffDispF
import ButtonBorderF
import ToggleGroupF
import GraphicsF(graphicsLabelF')
import Defaults(look3d, edgeWidth)
import FDefaults
toggleF :: Bool
-> [(ModState, KeySym)]
-> F a b
-> F (Either Bool a) (Either Bool b)
toggleF Bool
inside [(ModState, KeySym)]
keys F a b
lblF =
forall a b.
[(ModState, KeySym)]
-> F (Either (Either Bool Bool) a) b
-> F (Either Bool a) (Either Bool b)
toggleGroupF [(ModState, KeySym)]
keys forall a b. (a -> b) -> a -> b
$
if Bool
inside
then forall a b. Int -> F a b -> F (Either Bool a) b
buttonBorderF Int
edgew (forall {a} {b}. F a b -> F a b
mF F a b
lblF) forall c d e. F c d -> SP e c -> F e d
>=^^< forall {a1} {a2} {b}. SP a1 a2 -> SP (Either a1 b) (Either a2 b)
idRightSP forall {a1} {b}. SP (Either a1 b) b
filterRightSP
else forall {a}. Either a a -> a
stripEither forall a b e. (a -> b) -> F e a -> F e b
>^=< forall {a} {b}. F a b -> F a b
hBoxF (forall {a} {b}. F a b -> F a b
sF (forall a b. Int -> F a b -> F (Either Bool a) b
buttonBorderF Int
edgew forall {b}. F Bool b
indicatorF) forall {a} {b} {c} {d}.
F a b -> F c d -> F (Either a c) (Either b d)
>+< forall {a} {b}. F a b -> F a b
cF F a b
lblF)
where
indicatorF :: F Bool b
indicatorF = forall {a} {b}. F a b -> F a b
mF (forall nothing. Bool -> F Bool nothing
onOffDispF Bool
False)
mF :: F a b -> F a b
mF = forall {a} {b}. Int -> F a b -> F a b
marginF Int
innersep
sF :: F a b -> F a b
sF = forall {a} {b}. Spacer -> F a b -> F a b
spacer1F (Bool -> Bool -> Spacer
noStretchS Bool
True Bool
True Spacer -> Spacer -> Spacer
`compS` Spacer
vCenterS)
cF :: F a b -> F a b
cF = forall {a} {b}. Spacer -> F a b -> F a b
spacer1F (Bool -> Bool -> Spacer
noStretchS Bool
False Bool
True Spacer -> Spacer -> Spacer
`compS` Spacer
vCenterS)
innersep :: Int
innersep = Int
2
edgew :: Int
edgew = if Bool
look3d then Int
edgeWidth else forall a. Ord a => a -> a -> a
max Int
0 (Int
edgeWidthforall a. Num a => a -> a -> a
-Int
1)
oldToggleButtonF :: p -> [(ModState, KeySym)] -> p -> F Bool Bool
oldToggleButtonF p
x = forall {p} {p}.
(Graphic p, Show p, FontGen p) =>
Bool -> p -> [(ModState, KeySym)] -> p -> F Bool Bool
oldToggleButtonF' Bool
False p
x
oldToggleButtonF' :: Bool -> p -> [(ModState, KeySym)] -> p -> F Bool Bool
oldToggleButtonF' Bool
inside p
fname [(ModState, KeySym)]
keys p
lbl =
forall {a}. Either a a -> a
stripEither forall a b e. (a -> b) -> F e a -> F e b
>^=< forall {a} {b}.
Bool
-> [(ModState, KeySym)]
-> F a b
-> F (Either Bool a) (Either Bool b)
toggleF Bool
inside [(ModState, KeySym)]
keys forall {e} {d}. F e d
lblF forall c d e. F c d -> (e -> c) -> F e d
>=^< forall a b. a -> Either a b
Left
where
lblF :: F e d
lblF = forall {p} {e} {d}.
Graphic p =>
(GraphicsF p -> GraphicsF p) -> p -> F e d
graphicsLabelF' (forall {xxx} {a}.
(HasFontSpec xxx, Show a, FontGen a) =>
a -> Customiser xxx
setFont p
fname) p
lbl