Safe Haskell | None |
---|---|
Language | Haskell98 |
- data UISF b c :: * -> * -> *
- asyncV :: (NFData c, ArrowReader DeltaT a, ArrowCircuit a, ArrowIO a) => Double -> DeltaT -> PureAuto b c -> a b [(c, Time)]
- type Dimension = (Int, Int)
- topDown :: UISF a b -> UISF a b
- bottomUp :: UISF a b -> UISF a b
- leftRight :: UISF a b -> UISF a b
- rightLeft :: UISF a b -> UISF a b
- setSize :: Dimension -> UISF a b -> UISF a b
- setLayout :: Layout -> UISF a b -> UISF a b
- pad :: (Int, Int, Int, Int) -> UISF a b -> UISF a b
- defaultMUIParams :: UIParams
- data UIParams :: *
- runMUI :: UIParams -> UISF () () -> IO ()
- runMUI' :: UISF () () -> IO ()
- getTime :: UISF () Time
- label :: UITexty s => s -> UISF a a
- displayStr :: UISF String ()
- display :: Show a => UISF a ()
- withDisplay :: Show b => UISF a b -> UISF a b
- textboxE :: UITexty s => s -> UISF (SEvent s) String
- textbox :: UITexty s => s -> UISF (SEvent s) String
- title :: UITexty s => s -> UISF a b -> UISF a b
- button :: UITexty s => s -> UISF () Bool
- stickyButton :: UITexty s => s -> UISF () Bool
- checkbox :: UITexty s => s -> Bool -> UISF () Bool
- checkGroup :: [(String, a)] -> UISF () [a]
- radio :: UITexty s => [s] -> Int -> UISF () Int
- hSlider :: RealFrac a => (a, a) -> a -> UISF () a
- vSlider :: RealFrac a => (a, a) -> a -> UISF () a
- hiSlider :: Integral a => a -> (a, a) -> a -> UISF () a
- viSlider :: Integral a => a -> (a, a) -> a -> UISF () a
- realtimeGraph :: RealFrac a => Layout -> DeltaT -> Color -> UISF [(a, Time)] ()
- histogram :: RealFrac a => Layout -> UISF (SEvent [a]) ()
- listbox :: (Eq a, Show a) => [a] -> Int -> UISF (SEvent [a], SEvent Int) Int
- midiIn :: UISF (Maybe InputDeviceID) (SEvent [MidiMessage])
- midiOut :: UISF (Maybe OutputDeviceID, SEvent [MidiMessage]) ()
- midiInM :: UISF [InputDeviceID] (SEvent [MidiMessage])
- midiOutM :: UISF [(OutputDeviceID, SEvent [MidiMessage])] ()
- midiOutB :: UISF (Maybe OutputDeviceID, BufferOperation MidiMessage) Bool
- midiOutMB :: UISF [(OutputDeviceID, BufferOperation MidiMessage)] Bool
- data BufferOperation b :: * -> *
- = NoBOp
- | ClearBuffer
- | SkipAheadInBuffer DeltaT
- | MergeInBuffer [(DeltaT, b)]
- | AppendToBuffer [(DeltaT, b)]
- | SetBufferPlayStatus Bool (BufferOperation b)
- | SetBufferTempo Tempo (BufferOperation b)
- selectInput :: UISF () (Maybe InputDeviceID)
- selectOutput :: UISF () (Maybe OutputDeviceID)
- selectInputM :: UISF () [InputDeviceID]
- selectOutputM :: UISF () [OutputDeviceID]
- canvas :: Dimension -> UISF (SEvent Graphic) ()
- canvas' :: Layout -> (a -> Dimension -> Graphic) -> UISF (SEvent a) ()
- makeLayout :: LayoutType -> LayoutType -> Layout
- data LayoutType :: *
- data Color :: *
- = Black
- | Blue
- | Green
- | Cyan
- | Red
- | Magenta
- | Yellow
- | White
- | Gray
- | VLightBeige
- | LightBeige
- | MediumBeige
- | DarkBeige
Documentation
asyncV :: (NFData c, ArrowReader DeltaT a, ArrowCircuit a, ArrowIO a) => Double -> DeltaT -> PureAuto b c -> a b [(c, Time)] Source #
setSize :: Dimension -> UISF a b -> UISF a b #
A convenience function for setLayout, setSize sets the layout to a fixed size (in pixels).
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.
displayStr :: UISF String () #
DisplayStr is an output widget showing the instantaneous value of a signal of strings.
withDisplay :: Show b => UISF a b -> UISF a b #
withDisplay is a widget modifier that modifies the given widget so that it also displays its output value.
textbox :: UITexty s => s -> UISF (SEvent s) String #
The textbox widget creates a one line field where users can enter text. It supports mouse clicks and typing as well as the left, right, end, home, delete, and backspace special keys.
The value displayed can be generated by mouse and keyboard events, but it can also be set programmatically by providing the widget's input stream with an event containing the value to display. By using rec and delay, one can update the contents based on e.g. other widgets.
The static argument provides the textbox with initial text.
title :: UITexty s => s -> UISF a b -> UISF a b #
Title frames a UI by borders, and displays a static title text.
button :: UITexty s => s -> UISF () Bool #
A button is a focusable input widget with a state of being on or off. It can be activated with either a button press, the enter key, or the space key. 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 :: UITexty s => s -> UISF () Bool #
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 :: UITexty s => s -> Bool -> UISF () Bool #
Checkbox allows selection or deselection of an item. It has a static label as well as an initial state.
checkGroup :: [(String, a)] -> UISF () [a] #
The checkGroup widget creates a group of checkbox
es 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 :: UITexty s => [s] -> Int -> UISF () Int #
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.
realtimeGraph :: RealFrac a => Layout -> DeltaT -> Color -> UISF [(a, Time)] () #
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]) () #
The histogram widget creates a histogram of the input map. It assumes that the elements are to be displayed linearly and evenly spaced. Also, the values to be plotted must be between 0 and 1 (inclusive).
listbox :: (Eq a, Show a) => [a] -> Int -> UISF (SEvent [a], SEvent Int) Int #
The listbox widget creates a box with selectable entries. It takes two static values indicating the initial list of data to display and the initial index selected (use -1 for no selection). It takes two event streams that can be used to independently set the list and index. The output stream is the currently selected index.
Note that the index can be greater than the length of the list (simply indicating no choice selected).
midiIn :: UISF (Maybe InputDeviceID) (SEvent [MidiMessage]) Source #
midiOut :: UISF (Maybe OutputDeviceID, SEvent [MidiMessage]) () Source #
midiInM :: UISF [InputDeviceID] (SEvent [MidiMessage]) Source #
midiOutM :: UISF [(OutputDeviceID, SEvent [MidiMessage])] () Source #
data BufferOperation b :: * -> * #
The BufferOperation data type wraps up the data and operational commands
to control an eventbuffer
.
NoBOp | No Buffer Operation |
ClearBuffer | Erase the buffer |
SkipAheadInBuffer DeltaT | Skip ahead a certain amount of time in the buffer |
MergeInBuffer [(DeltaT, b)] | Merge data into the buffer |
AppendToBuffer [(DeltaT, b)] | Append data to the end of the buffer |
SetBufferPlayStatus Bool (BufferOperation b) | Set a new play status (True = Playing, False = Paused) |
SetBufferTempo Tempo (BufferOperation b) | Set the buffer's tempo |
selectInput :: UISF () (Maybe InputDeviceID) Source #
selectOutput :: UISF () (Maybe OutputDeviceID) Source #
selectInputM :: UISF () [InputDeviceID] Source #
selectOutputM :: UISF () [OutputDeviceID] Source #
canvas :: Dimension -> UISF (SEvent Graphic) () #
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) () #
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.
:: 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 :: * #
A dimension can either be:
We provide a data type for colors to allow users to easily and clearly specify common colors. Primary and secondary RGB colors are represented along with a few beige colors for use in many GUI elements.
Black | |
Blue | |
Green | |
Cyan | |
Red | |
Magenta | |
Yellow | |
White | |
Gray | |
VLightBeige | |
LightBeige | This is the default background color for the UI window. |
MediumBeige | |
DarkBeige |