module DynRadioGroupF where import Fudgets dynRadioGroupF :: [(b, lbl)] -> b -> F ([(b, lbl)], b) ([(b, lbl)], b) dynRadioGroupF [(b, lbl)] alts b startalt = forall {lbl} {b}. (Graphic lbl, Eq b) => Customiser RadioGroupF -> [(b, lbl)] -> b -> F ([(b, lbl)], b) ([(b, lbl)], b) dynRadioGroupF' forall a. Customiser a standard [(b, lbl)] alts b startalt dynRadioGroupF' :: Customiser RadioGroupF -> [(b, lbl)] -> b -> F ([(b, lbl)], b) ([(b, lbl)], b) dynRadioGroupF' Customiser RadioGroupF pm [(b, lbl)] alts b startalt = forall a b c d. F (Either a b) (Either c d) -> F c a -> F b d loopThroughRightF (forall {t} {a} {b}. (t -> a -> (t, [b])) -> t -> F a b mapstateF forall {b}. ([(b, lbl)], b) -> Either b ([(b, lbl)], b) -> (([(b, lbl)], b), [Either (Either (F b b) b) ([(b, lbl)], b)]) ctrl ([(b, lbl)] alts,b startalt)) (forall a b. F a b -> F (Either (F a b) a) b dynF ([(b, lbl)] -> b -> F b b rgF [(b, lbl)] alts b startalt)) where rgF :: [(b, lbl)] -> b -> F b b rgF = forall lbl alt. (Graphic lbl, Eq alt) => Customiser RadioGroupF -> [(alt, lbl)] -> alt -> F alt alt radioGroupF' Customiser RadioGroupF pm ctrl :: ([(b, lbl)], b) -> Either b ([(b, lbl)], b) -> (([(b, lbl)], b), [Either (Either (F b b) b) ([(b, lbl)], b)]) ctrl ([(b, lbl)] alts,b current) = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either forall {b} {a}. b -> (([(b, lbl)], b), [Either a ([(b, lbl)], b)]) fromRadioGroupF forall {b}. ([(b, lbl)], b) -> (([(b, lbl)], b), [Either (Either (F b b) b) b]) fromOutside where fromRadioGroupF :: b -> (([(b, lbl)], b), [Either a ([(b, lbl)], b)]) fromRadioGroupF b choice = (([(b, lbl)] alts,b choice),[forall a b. b -> Either a b Right ([(b, lbl)] alts,b choice)]) fromOutside :: ([(b, lbl)], b) -> (([(b, lbl)], b), [Either (Either (F b b) b) b]) fromOutside ([(b, lbl)] alts',b current') = (([(b, lbl)] alts',b current'), if forall a b. (a -> b) -> [a] -> [b] map forall a b. (a, b) -> a fst [(b, lbl)] alts' forall a. Eq a => a -> a -> Bool == forall a b. (a -> b) -> [a] -> [b] map forall a b. (a, b) -> a fst [(b, lbl)] alts then [forall a b. a -> Either a b Left (forall a b. b -> Either a b Right b current')] else [forall a b. a -> Either a b Left (forall a b. a -> Either a b Left ([(b, lbl)] -> b -> F b b rgF [(b, lbl)] alts' b current'))])