phooey-2.0: Functional user interfacesSource codeContentsIndex
Graphics.UI.Phooey.Monad
Portabilityportable
Stabilityprovisional
Maintainerconal@conal.net
Contents
The UI monad
Tools for high-level widgets
Some high-level widgets
Explicit layout
Description
A functional UI monad. Uses explicit data-driven "sources" of values. Supports recursive GUIs. See http://haskell.org/haskellwiki/Phooey#Monadic_Interface.
Synopsis
type CxLayout = CxMonoid Layout
type UI = ReaderT Win (WriterT CxLayout (WriterT (Source Action) IO))
type UI' a = Win -> IO ((a, CxLayout), Source Action)
biUI :: UI' a :<->: UI a
inUI :: (UI' a -> UI' b) -> (UI a -> UI b)
toUI :: UI' a -> UI a
fromUI :: UI b -> UI' b
type UIE a = UI (Event a)
type UIS a = UI (Source a)
runUI :: UI () -> IO ()
runNamedUI :: String -> UI () -> IO ()
act :: UI (Source Action) -> UI ()
type IWidget a = a -> UI (Source a)
type OWidget a = Source a -> UI ()
type OWidget' a = UI (Sink a)
type IOWidget a = (IWidget a, OWidget a, OWidget' a)
type MkWidget ctl a b = Unop Layout -> (Win -> [Prop ctl] -> IO ctl) -> Attr ctl a -> b
widgetL :: Widget w => Unop Layout -> w -> CxLayout
iwidget :: (Commanding ctl, Widget ctl) => MkWidget ctl a (IWidget a)
iwidget' :: Widget ctl => Event ctl (IO ()) -> MkWidget ctl a (IWidget a)
owidget :: Widget widget => MkWidget widget a (OWidget a)
owidget' :: Widget ctl => MkWidget ctl a (OWidget' a)
iowidget :: (Commanding widget, Widget widget) => MkWidget widget a (IOWidget a)
testWidget :: WioS a -> UI (Source a)
stringEntry :: IWidget String
stringDisplay :: OWidget String
stringDisplay' :: OWidget' String
showDisplay :: Show a => OWidget a
showDisplay' :: Show a => OWidget' a
islider :: (Int, Int) -> IWidget Int
isliderDisplay :: (Int, Int) -> OWidget Int
isliderDisplay' :: (Int, Int) -> OWidget' Int
fslider :: forall a. RealFrac a => (a, a) -> IWidget a
fsliderDisplay :: forall a. RealFrac a => (a, a) -> OWidget a
fsliderDisplay' :: forall a. RealFrac a => (a, a) -> OWidget' a
checkBoxEntry :: IWidget Bool
checkBoxDisplay :: OWidget Bool
checkBoxDisplay' :: OWidget' Bool
button :: a -> String -> UI (Event a)
button' :: a -> [Prop (Button ())] -> UI (Event a)
smallButton :: a -> String -> UI (Event a)
choices :: [String] -> IWidget String
timedPoll :: Double -> IO a -> UI (Source a)
fromTop :: Unop (UI a)
fromBottom :: Unop (UI a)
fromLeft :: Unop (UI a)
fromRight :: Unop (UI a)
The UI monad
type CxLayout = CxMonoid LayoutSource
Context-dependent layout
type UI = ReaderT Win (WriterT CxLayout (WriterT (Source Action) IO))Source
The UI monad
type UI' a = Win -> IO ((a, CxLayout), Source Action)Source
Convenient variation of UI
biUI :: UI' a :<->: UI aSource
Bijection for convenient manipulation.
inUI :: (UI' a -> UI' b) -> (UI a -> UI b)Source
Apply a unary function inside the UI representation.
toUI :: UI' a -> UI aSource
Make from representation
fromUI :: UI b -> UI' bSource
Extract representation
type UIE a = UI (Event a)Source
Event-valued UI
type UIS a = UI (Source a)Source
Source-valued UI
runUI :: UI () -> IO ()Source
Run a UI with window title "Monadic Phooey GUI".
runNamedUI :: String -> UI () -> IO ()Source
Run a UI with given window title.
act :: UI (Source Action) -> UI ()Source
Move an action source into position to be executed
Tools for high-level widgets
type IWidget a = a -> UI (Source a)Source
Input widget type (with initial value)
type OWidget a = Source a -> UI ()Source
Output widget type
type OWidget' a = UI (Sink a)Source
Alternative output widget type
type IOWidget a = (IWidget a, OWidget a, OWidget' a)Source
Combine input & output widget types
type MkWidget ctl a b = Unop Layout -> (Win -> [Prop ctl] -> IO ctl) -> Attr ctl a -> bSource
Utility type for making widgets
widgetL :: Widget w => Unop Layout -> w -> CxLayoutSource
iwidget :: (Commanding ctl, Widget ctl) => MkWidget ctl a (IWidget a)Source
Make an input widget. See alos 'iwidget\''.
iwidget' :: Widget ctl => Event ctl (IO ()) -> MkWidget ctl a (IWidget a)Source
Make an input widget with a given update event. If the update is commanding you can use iwidget.
owidget :: Widget widget => MkWidget widget a (OWidget a)Source
Make a high-level output widget
owidget' :: Widget ctl => MkWidget ctl a (OWidget' a)Source
Output widget, alternative style
iowidget :: (Commanding widget, Widget widget) => MkWidget widget a (IOWidget a)Source
Convenience function combining iwidget, owidget, and 'owidget\''
testWidget :: WioS a -> UI (Source a)Source
For testing out WinEvents
Some high-level widgets
stringEntry :: IWidget StringSource
String input widget
stringDisplay :: OWidget StringSource
String output widget
stringDisplay' :: OWidget' StringSource
Alternative string output widget
showDisplay :: Show a => OWidget aSource
Showable output widget
showDisplay' :: Show a => OWidget' aSource
Alternative showable output
islider :: (Int, Int) -> IWidget IntSource
Slider input widget
isliderDisplay :: (Int, Int) -> OWidget IntSource
Slider output widget
isliderDisplay' :: (Int, Int) -> OWidget' IntSource
Alternative slider output widget
fslider :: forall a. RealFrac a => (a, a) -> IWidget aSource
Fractional slider, alternative interface
fsliderDisplay :: forall a. RealFrac a => (a, a) -> OWidget aSource
Fractional slider
fsliderDisplay' :: forall a. RealFrac a => (a, a) -> OWidget' aSource
Fractional slider, alternative interface
checkBoxEntry :: IWidget BoolSource
Boolean input widget
checkBoxDisplay :: OWidget BoolSource
Boolean output widget
checkBoxDisplay' :: OWidget' BoolSource
Alternative Boolean output widget
button :: a -> String -> UI (Event a)Source
Simple button with value & label. Use 'button\'' for custom properties.
button' :: a -> [Prop (Button ())] -> UI (Event a)Source
Button with value & properties. If you just want a label, use button.
smallButton :: a -> String -> UI (Event a)Source
Minimal size button with value & label
choices :: [String] -> IWidget StringSource
Input from a "menu" of string choices.
timedPoll :: Double -> IO a -> UI (Source a)Source
Input from a timer and a means of polling. Interval is in seconds. If poll is expensive, then apply cache to the resulting UI.
Explicit layout
fromTop :: Unop (UI a)Source
fromBottom :: Unop (UI a)Source
fromLeft :: Unop (UI a)Source
fromRight :: Unop (UI a)Source
Produced by Haddock version 2.1.0