fudgets-0.18.3.2: The Fudgets Library
Safe HaskellNone
LanguageHaskell98

ContribFudgets

Description

Contributed add-ons to the Fudget Library

Synopsis

Contributed add-ons to the Fudget Library

radioF1 :: Eq a => RadioButtonBorderType -> FontName -> [(a, String)] -> a -> F a a Source #

radioGroupF1 :: Eq a => RadioButtonBorderType -> FontName -> [a] -> a -> (a -> String) -> F a a Source #

toggleF1 :: RBBT -> [(ModState, KeySym)] -> F a b -> F (Either Bool a) (Either Bool b) Source #

toggleButtonF1 :: RadioButtonBorderType -> String -> [(ModState, KeySym)] -> String -> F Bool Bool Source #

data RBBT Source #

Constructors

Circle 
Square 
Triangle 

titleShellF :: [Char] -> F c d -> F (Either String c) d Source #

titleShellF' :: (ShellF -> ShellF) -> [Char] -> F c d -> F (Either String c) d Source #

wmShellF :: [Char] -> F c d -> F (Either (Either String Bool) c) (Either () d) Source #

wmShellF' :: (ShellF -> ShellF) -> [Char] -> F c d -> F (Either (Either String Bool) c) (Either () d) Source #

auxShellF :: [Char] -> F c b -> F (Either Bool c) (Either Bool b) Source #

delayedAuxShellF' :: (ShellF -> ShellF) -> [Char] -> F c b -> F (Either Bool c) (Either Bool b) Source #

auxShellF' :: (ShellF -> ShellF) -> [Char] -> F c b -> F (Either Bool c) (Either Bool b) Source #

menuF :: Eq a => Menu a -> F a a Source #

menuBarF :: Eq a => Menu a -> F a a Source #

type MenuBar a = Menu a Source #

type Menu a = [MenuItem' a] Source #

data Item a Source #

Instances

Instances details
Eq a => Eq (Item a) Source # 
Instance details

Defined in MenuBarF

Methods

(==) :: Item a -> Item a -> Bool #

(/=) :: Item a -> Item a -> Bool #

Graphic (Item a) Source # 
Instance details

Defined in MenuBarF

item :: Graphic a1 => a2 -> a1 -> Item a2 Source #

item' :: Graphic a1 => Keys -> a2 -> a1 -> Item a2 Source #

key :: Item a -> [Char] -> Item a Source #

cmdItem :: Graphic a1 => a2 -> a1 -> Item (MenuItem a2) Source #

subMenuItem :: (Graphic a1, Eq b) => Transl b a2 -> Menu b -> a1 -> Item (MenuItem a2) Source #

toggleItem :: Graphic a1 => Transl Bool a2 -> Bool -> a1 -> Item (MenuItem a2) Source #

radioGroupItem :: (Graphic a1, Eq b) => Transl b a2 -> [Item b] -> b -> a1 -> Item (MenuItem a2) Source #

dynRadioGroupItem :: (Graphic a1, Eq b) => Transl ([Item b], b) a2 -> [Item b] -> b -> a1 -> Item (MenuItem a2) Source #

delayedSubMenuItem :: (Graphic a1, Eq b) => Transl b a2 -> Menu b -> a1 -> Item (MenuItem a2) Source #

data MenuItem a Source #

Constructors

MenuCommand a 
MenuToggle (Transl Bool a) Bool 
forall b.Eq b => MenuRadioGroup (Transl b a) [Item b] b 
forall b.Eq b => MenuDynRadioGroup (Transl ([Item b], b) a) [Item b] b 
forall b.Eq b => SubMenu Bool (Transl b a) (Menu b) 
MenuLabel 

menu :: Eq b => Transl b a -> Menu b -> MenuItem a Source #

data Transl l g Source #

Constructors

Transl (l -> g) (g -> Maybe l) 

compT :: Transl l g -> Transl c l -> Transl c g Source #

helpBubbleF :: Graphic g => g -> F c d -> F c d Source #

fileShellF :: (c1 -> String, String -> Either String c1, Maybe c1) -> [Char] -> F c1 (InputMsg c1) -> F c2 d Source #

fileShellF' :: (ShellF -> ShellF) -> (c1 -> String, String -> Either String c1, Maybe c1) -> [Char] -> F c1 (InputMsg c1) -> F c2 d Source #

showReadFileShellF :: (Show a, Read a) => Maybe a -> [Char] -> F a (InputMsg a) -> F c d Source #

showReadFileShellF' :: (Show a, Read a) => (ShellF -> ShellF) -> Maybe a -> [Char] -> F a (InputMsg a) -> F c d Source #

popup :: ([Char], Maybe a) Source #

completeFromList :: Eq a => [[a]] -> [a] -> [([a], [a])] Source #

completionStringF :: F (Either ([Char] -> [(a, [Char])]) [Char]) (Either [(a, [Char])] (InputMsg [Char])) Source #

completionStringF' :: Char -> Customiser StringF -> F (Either ([Char] -> [(a, [Char])]) [Char]) (Either [(a, [Char])] (InputMsg [Char])) Source #

hSplitF :: F a1 a2 -> F c b -> F (Either a1 c) (Either a2 b) Source #

vSplitF :: F a1 a2 -> F c b -> F (Either a1 c) (Either a2 b) Source #

hSplitF' :: Double -> F a1 a2 -> F c b -> F (Either a1 c) (Either a2 b) Source #

vSplitF' :: Double -> F a1 a2 -> F c b -> F (Either a1 c) (Either a2 b) Source #

splitF' :: LayoutDir -> Double -> F a1 a2 -> F c b -> F (Either a1 c) (Either a2 b) Source #

data ClientMsg a Source #

Constructors

ClientMsg a 
ClientEOS 
ClientNew 

Instances

Instances details
Show a => Show (ClientMsg a) Source # 
Instance details

Defined in SocketServer

data SocketMsg a Source #

Constructors

SocketMsg a 
SocketEOS 

Instances

Instances details
Functor SocketMsg Source # 
Instance details

Defined in SocketServer

Methods

fmap :: (a -> b) -> SocketMsg a -> SocketMsg b #

(<$) :: a -> SocketMsg b -> SocketMsg a #

Show a => Show (SocketMsg a) Source # 
Instance details

Defined in SocketServer

mapSocketMsg :: (t -> a) -> SocketMsg t -> SocketMsg a Source #

socketServerF :: Int -> (Socket -> Peer -> F a1 (SocketMsg a2)) -> F (Int, a1) (Int, ClientMsg a2) Source #

module ConnectF

module ReactiveF