module EndButtonsF where import AllFudgets endButtonsF :: F (Either Click Click) (Either Click Click) endButtonsF = forall {a} {b}. Bool -> Bool -> F a b -> F a b noStretchF Bool False Bool True forall a b. (a -> b) -> a -> b $ forall {a} {b}. Int -> F a b -> F a b matrixF Int 2 (F Click Click ok forall {a} {b} {c} {d}. F a b -> F c d -> F (Either a c) (Either b d) >+< F Click Click cancel) where ok :: F Click Click ok = forall {lbl}. Graphic lbl => lbl -> F Click Click buttonF String "OK" cancel :: F Click Click cancel = forall {lbl}. Graphic lbl => Customiser (ButtonF lbl) -> lbl -> F Click Click buttonF' Customiser (ButtonF String) pm String "Cancel" where pm :: Customiser (ButtonF String) pm = forall xxx. HasKeys xxx => [(ModState, String)] -> Customiser xxx setKeys [([],String "Escape")] endButtonsF' :: F String (Either Click Click) endButtonsF' = forall {a} {b}. Bool -> Bool -> F a b -> F a b noStretchF Bool False Bool True forall a b. (a -> b) -> a -> b $ forall {a} {b}. Int -> F a b -> F a b matrixF Int 2 (F String Click ok forall {a} {b} {c} {d}. F a b -> F c d -> F (Either a c) (Either b d) >+< F Click Click cancel) forall c d e. F c d -> (e -> c) -> F e d >=^< forall a b. a -> Either a b Left where ok :: F String Click ok = forall lbl. Graphic lbl => Customiser (ButtonF lbl) -> lbl -> PF (ButtonF lbl) Click Click buttonF'' forall a. Customiser a standard String "OK" forall c d e. F c d -> (e -> c) -> F e d >=^< forall a b. a -> Either a b Left forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {lbl}. lbl -> Customiser (ButtonF lbl) setLabel forall c d e. F c d -> SP e c -> F e d >=^^< forall a. Eq a => SP a a idempotSP cancel :: F Click Click cancel = forall {lbl}. Graphic lbl => Customiser (ButtonF lbl) -> lbl -> F Click Click buttonF' Customiser (ButtonF String) pm String "Cancel" where pm :: Customiser (ButtonF String) pm = forall xxx. HasKeys xxx => [(ModState, String)] -> Customiser xxx setKeys [([],String "Escape")]