UISF-0.3.0.2: Library for Arrowized Graphical User Interfaces.

Safe HaskellNone
LanguageHaskell98

FRP.UISF

Synopsis

Documentation

runUI' :: UISF () () -> IO () Source

Run the UISF with the default settings.

runUI :: UIParams -> UISF () () -> IO () Source

Run the UISF with the given parameters.

data UIParams Source

The UIParams data type provides an interface for modifying some of the settings for runUI without forcing runUI to take a zillion arguments. Typical usage will be to modify the below defaultUIParams using record syntax.

Constructors

UIParams 

Fields

uiInitialize :: IO ()

An initialization action.

uiClose :: IO ()

A termination action.

uiTitle :: String

The UI window's title.

uiSize :: Dimension

The size of the UI window.

uiInitFlow :: Flow

The initial Flow setting.

uiTickDelay :: Double

How long the UI will sleep between clock ticks if no events are detected. This should be probably be set to O(milliseconds), but it can be set to 0 for better performance (but also higher CPU usage)

defaultUIParams :: UIParams Source

This is the default UIParams value and what is used in runUI'.

type Dimension = (Int, Int) Source

A dimension specifies size.

label :: String -> UISF a a Source

Labels are always left aligned and vertically centered.

displayStr :: UISF String () Source

DisplayStr is an output widget showing the instantaneous value of a signal of strings.

display :: Show a => UISF a () Source

display is a widget that takes any show-able value and displays it.

withDisplay :: Show b => UISF a b -> UISF a b Source

withDisplay is a widget modifier that modifies the given widget so that it also displays its output value.

textbox :: UISF String String Source

Textbox is a widget showing the instantaneous value of a signal of strings.

The textbox widget will often be used with ArrowLoop (the rec keyword). However, it uses delay internally, so there should be no fear of a blackhole.

The textbox widget supports mouse clicks and typing as well as the left, right, end, home, delete, and backspace special keys.

textboxE :: String -> UISF (SEvent String) String Source

This variant of the textbox takes a static argument that is the initial value in the textbox. Then, it takes a stream of 'SEvent String' and only externally updates the contents of the textbox when an event occurs.

title :: String -> UISF a b -> UISF a b Source

Title frames a UI by borders, and displays a static title text.

button :: String -> UISF () Bool Source

A button is a focusable input widget with a state of being on or off. It can be activated with either a button press or the enter key. (Currently, there is no support for the space key due to non-special keys not having Release events.) Buttons also show a static label.

The regular button is down as long as the mouse button or key press is down and then returns to up.

stickyButton :: String -> UISF () Bool Source

The sticky button, on the other hand, once pressed, remains depressed until is is clicked again to be released. Thus, it looks like a button, but it behaves more like a checkbox.

checkbox :: String -> Bool -> UISF () Bool Source

Checkbox allows selection or deselection of an item. It has a static label as well as an initial state.

checkGroup :: [(String, a)] -> UISF () [a] Source

The checkGroup widget creates a group of checkboxes that all send their outputs to the same output stream. It takes a static list of labels for the check boxes and assumes they all start unchecked.

The output stream is a list of each a value that was paired with a String value for which the check box is checked.

radio :: [String] -> Int -> UISF () Int Source

Radio button presents a list of choices and only one of them can be selected at a time. It takes a static list of choices (as Strings) and the index of the initially selected one, and the widget itself returns the continuous stream representing the index of the selected choice.

hSlider :: RealFrac a => (a, a) -> a -> UISF () a Source

Horizontal Continuous Slider

vSlider :: RealFrac a => (a, a) -> a -> UISF () a Source

Vertical Continuous Slider

hiSlider :: Integral a => a -> (a, a) -> a -> UISF () a Source

Horizontal Discrete Slider

viSlider :: Integral a => a -> (a, a) -> a -> UISF () a Source

Vertical Discrete Slider

realtimeGraph :: RealFrac a => Layout -> Time -> Color -> UISF [(a, Time)] () Source

The realtimeGraph widget creates a graph of the data with trailing values. It takes a dimension parameter, the length of the history of the graph measured in time, and a color for the graphed line. The signal function then takes an input stream of (value,time) event pairs, but since there can be zero or more points at once, we use [] rather than SEvent for the type. The values in the (value,time) event pairs should be between -1 and 1.

histogram :: RealFrac a => Layout -> UISF (SEvent [a]) () Source

The histogram widget creates a histogram of the input map. It assumes that the elements are to be displayed linearly and evenly spaced.

histogramWithScale :: RealFrac a => Layout -> UISF (SEvent [(a, String)]) () Source

The histogramWithScale widget creates a histogram and an x coordinate scale.

listbox :: (Eq a, Show a) => UISF ([a], Int) Int Source

The listbox widget creates a box with selectable entries. The input stream is the list of entries as well as which entry is currently selected, and the output stream is the index of the newly selected entry. Note that the index can be greater than the length of the list (simply indicating no choice selected).

canvas :: Dimension -> UISF (SEvent Graphic) () Source

Canvas displays any graphics. The input is a signal of graphics events because we only want to redraw the screen when the input is there.

canvas' :: Layout -> (a -> Dimension -> Graphic) -> UISF (SEvent a) () Source

canvas' uses a layout and a graphic generator. This allows it to behave similarly to canvas, but it can adjust in cases with stretchy layouts.

topDown :: UISF a b -> UISF a b Source

bottomUp :: UISF a b -> UISF a b Source

leftRight :: UISF a b -> UISF a b Source

rightLeft :: UISF a b -> UISF a b Source

pad :: (Int, Int, Int, Int) -> UISF a b -> UISF a b Source

Add space padding around a widget.

setSize :: Dimension -> UISF a b -> UISF a b Source

A convenience function for setLayout, setSize sets the layout to a fixed size (in pixels).

setLayout :: Layout -> UISF a b -> UISF a b Source

Set a new layout for this widget.

makeLayout Source

Arguments

:: LayoutType

Horizontal Layout information

-> LayoutType

Vertical Layout information

-> Layout 

Layouts for individual widgets typically come in a few standard flavors, so we have this convenience function for their creation. This function takes layout information for first the horizontal dimension and then the vertical.

data LayoutType Source

A dimension can either be:

Constructors

Stretchy

Stretchy with a minimum size in pixels

Fields

minSize :: Int
 
Fixed

Fixed with a size measured in pixels

Fields

fixedSize :: Int
 

getTime :: UISF () Time Source

Get the time signal from a UISF.

asyncUISFV :: NFData b => Double -> Double -> Automaton (->) a b -> UISF a [(b, Time)] Source

This is the standard one that appropriately keeps track of simulated time vs real time.

The clockrate is the simulated rate of the input signal function. The buffer is the number of time steps the given signal function is allowed to get ahead of real time. The real amount of time that it can get ahead is the buffer divided by the clockrate seconds. The output signal function takes and returns values in real time. The return values are the list of bs generated in the given time step, each time stamped.

Note that the returned list may be long if the clockrate is much faster than real time and potentially empty if it's slower. Note also that the caller can check the time stamp on the element at the end of the list to see if the inner, "simulated" signal function is performing as fast as it should.

asyncUISFE :: NFData b => Automaton (->) a b -> UISF (SEvent a) (SEvent b) Source

We can also lift a signal function to a UISF asynchronously.