Safe Haskell | None |
---|---|
Language | Haskell98 |
Primitive GUI elements.
There is a convention that constructors take only parameters that specify the logic of the widget. The view is set for GUI-elements with other functions.
- data ValDiap :: * = ValDiap {
- valDiapMin :: Double
- valDiapMax :: Double
- type ValStep = Double
- data ValScaleType :: *
- data ValSpan :: * = ValSpan {}
- linSpan :: Double -> Double -> ValSpan
- expSpan :: Double -> Double -> ValSpan
- uspan :: ValSpan
- bspan :: ValSpan
- uspanExp :: ValSpan
- count :: ValDiap -> ValStep -> Maybe ValStep -> Double -> Source (Evt D)
- countSig :: ValDiap -> ValStep -> Maybe ValStep -> Double -> Source Sig
- joy :: ValSpan -> ValSpan -> (Double, Double) -> Source (Sig, Sig)
- knob :: String -> ValSpan -> Double -> Source Sig
- data KnobType :: *
- setKnobType :: KnobType -> Gui -> Gui
- roller :: String -> ValSpan -> ValStep -> Double -> Source Sig
- slider :: String -> ValSpan -> Double -> Source Sig
- sliderBank :: String -> [Double] -> Source [Sig]
- data SliderType :: *
- setSliderType :: SliderType -> Gui -> Gui
- numeric :: String -> ValDiap -> ValStep -> Double -> Source Sig
- data TextType :: *
- = NormalText
- | NoDrag
- | NoEdit
- setTextType :: TextType -> Gui -> Gui
- box :: String -> Display
- data BoxType :: *
- setBoxType :: BoxType -> Gui -> Gui
- button :: String -> Source (Evt Unit)
- data ButtonType :: *
- setButtonType :: ButtonType -> Gui -> Gui
- toggle :: String -> Bool -> Source (Evt D)
- butBank :: String -> Int -> Int -> (Int, Int) -> Source (Evt (D, D))
- toggleSig :: String -> Bool -> Source Sig
- butBankSig :: String -> Int -> Int -> (Int, Int) -> Source (Sig, Sig)
- butBank1 :: String -> Int -> Int -> (Int, Int) -> Source (Evt D)
- butBankSig1 :: String -> Int -> Int -> (Int, Int) -> Source Sig
- radioButton :: Arg a => String -> [(String, a)] -> Int -> Source (Evt a)
- matrixButton :: Arg a => String -> Int -> Int -> [a] -> (Int, Int) -> Source (Evt a)
- funnyRadio :: Tuple b => String -> [(String, a -> b)] -> Int -> Source (a -> b)
- funnyMatrix :: Tuple b => String -> Int -> Int -> [a -> b] -> (Int, Int) -> Source (a -> b)
- setNumeric :: String -> ValDiap -> ValStep -> Double -> Sink Sig
- meter :: String -> ValSpan -> Double -> Sink Sig
- setKnob :: String -> ValSpan -> Double -> SinkSource Sig
- setSlider :: String -> ValSpan -> Double -> SinkSource Sig
- setToggle :: String -> Bool -> SinkSource (Evt D)
- setToggleSig :: String -> Bool -> SinkSource Sig
- setTitle :: String -> Gui -> SE Gui
- data KeyEvt :: *
- data Key :: *
- = CharKey Char
- | F1
- | F2
- | F3
- | F4
- | F5
- | F6
- | F7
- | F8
- | F9
- | F10
- | F11
- | F12
- | Scroll
- | CapsLook
- | LeftShift
- | RightShift
- | LeftCtrl
- | RightCtrl
- | Enter
- | LeftAlt
- | RightAlt
- | LeftWinKey
- | RightWinKey
- | Backspace
- | ArrowUp
- | ArrowLeft
- | ArrowRight
- | ArrowDown
- | Insert
- | Home
- | PgUp
- | Delete
- | End
- | PgDown
- | NumLock
- | NumDiv
- | NumMul
- | NumSub
- | NumHome
- | NumArrowUp
- | NumPgUp
- | NumArrowLeft
- | NumSpace
- | NumArrowRight
- | NumEnd
- | NumArrowDown
- | NumPgDown
- | NumIns
- | NumDel
- | NumEnter
- | NumPlus
- | Num7
- | Num8
- | Num9
- | Num4
- | Num5
- | Num6
- | Num1
- | Num2
- | Num3
- | Num0
- | NumDot
- keyIn :: KeyEvt -> Evt Unit
- charOn :: Char -> Evt Unit
- charOff :: Char -> Evt Unit
- strOn :: String -> Tick
- strOff :: String -> Tick
- uknob :: Double -> Source Sig
- xknob :: Range Double -> Double -> Source Sig
- uslider :: Double -> Source Sig
- xslider :: Range Double -> Double -> Source Sig
- ujoy :: (Double, Double) -> Source (Sig, Sig)
- hradio :: [String] -> Int -> Source (Evt D)
- vradio :: [String] -> Int -> Source (Evt D)
- hradioSig :: [String] -> Int -> Source Sig
- vradioSig :: [String] -> Int -> Source Sig
- hnumbers :: [Double] -> Source Sig
- vnumbers :: [Double] -> Source Sig
- type Range a = (a, a)
- rangeKnob :: Bool -> Range Int -> Int -> Source (Evt D)
- rangeSlider :: Bool -> Range Int -> Int -> Source (Evt D)
- rangeKnobSig :: Range Int -> Int -> Source Sig
- rangeSliderSig :: Range Int -> Int -> Source Sig
- rangeJoy :: Bool -> Range Int -> Range Int -> (Int, Int) -> Source (Evt D, Evt D)
- rangeJoy2 :: Bool -> Range Int -> Range Int -> (Int, Int) -> Source (Evt (D, D))
- rangeJoySig :: Range Int -> Range Int -> (Int, Int) -> Source (Sig, Sig)
- knobPad :: Int -> Int -> [String] -> [Double] -> Source (Int -> Int -> Sig)
- togglePad :: Int -> Int -> [String] -> [Bool] -> Source (Int -> Int -> Evt D)
- buttonPad :: Int -> Int -> [String] -> Source (Int -> Int -> Evt Unit)
- genPad :: (String -> a -> Source b) -> a -> Int -> Int -> [String] -> [a] -> Source (Int -> Int -> b)
- button' :: Tick -> String -> Source Tick
- toggle' :: Evt D -> String -> Bool -> Source (Evt D)
- toggleSig' :: Sig -> String -> Bool -> Source Sig
- knob' :: Sig -> String -> ValSpan -> Double -> Source Sig
- slider' :: Sig -> String -> ValSpan -> Double -> Source Sig
- uknob' :: Sig -> Double -> Source Sig
- uslider' :: Sig -> Double -> Source Sig
- hradio' :: Evt D -> [String] -> Int -> Source (Evt D)
- vradio' :: Evt D -> [String] -> Int -> Source (Evt D)
- hradioSig' :: Sig -> [String] -> Int -> Source Sig
- vradioSig' :: Sig -> [String] -> Int -> Source Sig
Common properties
The diapason of the continuous value.
ValDiap | |
|
data ValScaleType :: * #
A value span is a diapason of the value and a type of the scale (can be linear or exponential).
linSpan :: Double -> Double -> ValSpan #
Makes a linear ValSpan
with specified boundaries.
linSpan minVal maxVal
expSpan :: Double -> Double -> ValSpan #
Makes an exponential ValSpan
with specified boundaries.
expSpan minVal maxVal
Valuators
count :: ValDiap -> ValStep -> Maybe ValStep -> Double -> Source (Evt D) #
Allows the user to increase/decrease a value with mouse clicks on a corresponding arrow button. Output is an event stream that contains values when counter changes.
count diapason fineValStep maybeCoarseValStep initValue
countSig :: ValDiap -> ValStep -> Maybe ValStep -> Double -> Source Sig #
A variance on the function count
, but it produces
a signal of piecewise constant function.
joy :: ValSpan -> ValSpan -> (Double, Double) -> Source (Sig, Sig) #
It is a squared area that allows the user to modify two output values at the same time. It acts like a joystick.
joy valueSpanX valueSpanY (initX, initY)
knob :: String -> ValSpan -> Double -> Source Sig #
A FLTK widget opcode that creates a knob.
knob valueSpan initValue
setKnobType :: KnobType -> Gui -> Gui #
roller :: String -> ValSpan -> ValStep -> Double -> Source Sig #
FLroller is a sort of knob, but put transversally.
roller valueSpan step initVal
slider :: String -> ValSpan -> Double -> Source Sig #
FLslider puts a slider into the corresponding container.
slider valueSpan initVal
sliderBank :: String -> [Double] -> Source [Sig] #
Constructs a list of linear unit sliders (ranges in [0, 1]). It takes a list of init values.
setSliderType :: SliderType -> Gui -> Gui #
numeric :: String -> ValDiap -> ValStep -> Double -> Source Sig #
numeric (originally FLtext in the Csound) allows the user to modify a parameter value by directly typing it into a text field.
numeric diapason step initValue
setTextType :: TextType -> Gui -> Gui #
Other widgets
A FLTK widget that displays text inside of a box. If the text is longer than 255 characters the text is split on several parts (Csound limitations).
box text
The type of the box. Some values are not implemented on the Csound level.
setBoxType :: BoxType -> Gui -> Gui #
data ButtonType :: * #
The type of the button. It affects toggle buttons and button banks.
In Csound buttons and toggle buttons
are constructed with the same function (but with different button types).
But in this library they are contructed by different functions (button
and toggle
).
Normal button is a plain old button, but other values specify toggle buttons.
So this property doesn't affect the buttons (since they could be only normal buttons).
setButtonType :: ButtonType -> Gui -> Gui #
toggle :: String -> Bool -> Source (Evt D) #
A FLTK widget opcode that creates a toggle button.
button text
butBank :: String -> Int -> Int -> (Int, Int) -> Source (Evt (D, D)) #
A FLTK widget opcode that creates a bank of buttons. Result is (x, y) coordinate of the triggered button.
butBank xNumOfButtons yNumOfButtons
toggleSig :: String -> Bool -> Source Sig #
A variance on the function toggle
, but it produces
a signal of piecewise constant function.
butBankSig :: String -> Int -> Int -> (Int, Int) -> Source (Sig, Sig) #
A variance on the function butBank
, but it produces
a signal of piecewise constant function.
Result is (x, y) coordinate of the triggered button.
butBank1 :: String -> Int -> Int -> (Int, Int) -> Source (Evt D) #
A FLTK widget opcode that creates a bank of buttons.
butBank xNumOfButtons yNumOfButtons
radioButton :: Arg a => String -> [(String, a)] -> Int -> Source (Evt a) Source #
A radio button. It takes a list of values with labels.
matrixButton :: Arg a => String -> Int -> Int -> [a] -> (Int, Int) -> Source (Evt a) Source #
A matrix of values.
funnyRadio :: Tuple b => String -> [(String, a -> b)] -> Int -> Source (a -> b) Source #
Radio button that returns functions. Useful for picking a waveform or type of filter.
funnyMatrix :: Tuple b => String -> Int -> Int -> [a -> b] -> (Int, Int) -> Source (a -> b) Source #
Matrix of functional values.
setNumeric :: String -> ValDiap -> ValStep -> Double -> Sink Sig #
FLtext that is sink shows current the value of a valuator in a text field.
meter :: String -> ValSpan -> Double -> Sink Sig #
A slider that serves as indicator. It consumes values instead of producing.
meter valueSpan initValue
setToggleSig :: String -> Bool -> SinkSource Sig #
Transformers
Keyboard
Keys.
strOn :: String -> Tick Source #
Creates an event in the output stream when one of the chars is pressed.
strOff :: String -> Tick Source #
Creates an event in the output stream when one of the chars is depressed.
Easy to use widgets
uknob :: Double -> Source Sig Source #
Unipolar linear knob. The value belongs to the interval [0, 1]. The argument is for initial value.
xknob :: Range Double -> Double -> Source Sig Source #
Exponential knob (usefull for exploring frequencies or decibels).
xknob (min, max) initVal
The value belongs to the interval [min, max]. The last argument is for initial value.
uslider :: Double -> Source Sig Source #
Unipolar linear slider. The value belongs to the interval [0, 1]. The argument is for initial value.
xslider :: Range Double -> Double -> Source Sig Source #
Exponential slider (usefull for exploring frequencies or decibels).
xknob (min, max) initVal
The value belongs to the interval [min, max]. The last argument is for initial value.
Number selectors
Widgets for sample and hold functions
hnumbers :: [Double] -> Source Sig Source #
The sample and hold widget. You can pick a value from the list of doubles.
The original value is a head of the list (the first element).
The visual grouping is horizontal (notice the prefix h
).
It's common to use it with function selector
.
vnumbers :: [Double] -> Source Sig Source #
The sample and hold widget. You can pick a value from the list of doubles.
The original value is a head of the list (the first element).
The visual grouping is vertical (notice the prefix v
).
It's common to use it with function selector
.
Range widgets
rangeKnob :: Bool -> Range Int -> Int -> Source (Evt D) Source #
Creates a knob that outputs only integers in the given range.
It produces an event stream of integer values. It can be used with
list access functions listAt
, atTuple
, atArg
.
rangeKnob needInit (min, max) initVal
The first argument is a boolean. If it's true than the initial value is put in the output stream. If its False the initial value is skipped.
rangeSlider :: Bool -> Range Int -> Int -> Source (Evt D) Source #
Creates a slider that outputs only integers in the given range.
It produces an event stream of integer values. It can be used with
list access functions listAt
, atTuple
, atArg
.
rangeSlider needInit (min, max) initVal
The first argument is a boolean. If it's true than the initial value is put in the output stream. If its False the initial value is skipped.
rangeKnobSig :: Range Int -> Int -> Source Sig Source #
Creates a knob that outputs only integers in the given range. It produces a signal of integer values.
rangeKnobSig (min, max) initVal
rangeSliderSig :: Range Int -> Int -> Source Sig Source #
Creates a slider that outputs only integers in the given range. It produces a signal of integer values.
rangeSliderSig (min, max) initVal
rangeJoy :: Bool -> Range Int -> Range Int -> (Int, Int) -> Source (Evt D, Evt D) Source #
2d range range slider. Outputs a pair of event streams. Each stream contains changes in the given direction (Ox or Oy).
rangeJoy needsInit rangeX rangeY (initX, initY)
The first argument is a boolean. If it's true than the initial value is put in the output stream. If its False the initial value is skipped.
rangeJoy2 :: Bool -> Range Int -> Range Int -> (Int, Int) -> Source (Evt (D, D)) Source #
2d range range slider. It produces a single event stream. The event fires when any signal changes.
rangeJoy2 needsInit rangeX rangeY (initX, initY)
The first argument is a boolean. If it's true than the initial value is put in the output stream. If its False the initial value is skipped.
rangeJoySig :: Range Int -> Range Int -> (Int, Int) -> Source (Sig, Sig) Source #
2d range range slider. It produces the pair of integer signals
The 2D matrix of widgets
knobPad :: Int -> Int -> [String] -> [Double] -> Source (Int -> Int -> Sig) Source #
The matrix of unipolar knobs.
knobPad columnNum rowNum names initVals
It takes in the dimensions of matrix, the names (we can leave it empty if names are not important) and list of init values. It returns a function that takes in indices and produces the signal in the corresponding cell.
togglePad :: Int -> Int -> [String] -> [Bool] -> Source (Int -> Int -> Evt D) Source #
The matrix of toggle buttons.
togglePad columnNum rowNum names initVals
It takes in the dimensions of matrix, the names (we can leave it empty if names are not important) and list of init values (on/off booleans). It returns a function that takes in indices and produces the event stream in the corresponding cell.
buttonPad :: Int -> Int -> [String] -> Source (Int -> Int -> Evt Unit) Source #
The matrix of buttons.
buttonPad columnNum rowNum names
It takes in the dimensions of matrix, the names (we can leave it empty if names are not important). It returns a function that takes in indices and produces the event stream in the corresponding cell.
genPad :: (String -> a -> Source b) -> a -> Int -> Int -> [String] -> [a] -> Source (Int -> Int -> b) Source #
A generic constructor for matrixes of sound source widgets. It takes the constructor of the widget, a default initial value, the dimensions of the matrix, the list of names and the list of initial values. It produces the function that maps indices to corresponding values.
External control
The widgets can be controlled with external signals/event streams
button' :: Tick -> String -> Source Tick Source #
It's like simple button
, but it can be controlled with external control.
The first argument is for external control.
toggle' :: Evt D -> String -> Bool -> Source (Evt D) Source #
It's like simple toggle
, but it can be controlled with external control.
The first argument is for external control.
knob' :: Sig -> String -> ValSpan -> Double -> Source Sig Source #
It's like simple knob
, but it can be controlled with external control.
The first argument is for external control.
slider' :: Sig -> String -> ValSpan -> Double -> Source Sig Source #
It's like simple slider
, but it can be controlled with external control.
The first argument is for external control.
uknob' :: Sig -> Double -> Source Sig Source #
It's like simple uknob
, but it can be controlled with external control.
The first argument is for external control.
uslider' :: Sig -> Double -> Source Sig Source #
It's like simple uslider
, but it can be controlled with external control.
The first argument is for external control.
hradio' :: Evt D -> [String] -> Int -> Source (Evt D) Source #
It's like simple hradio
, but it can be controlled with external control.
The first argument is for external control.
vradio' :: Evt D -> [String] -> Int -> Source (Evt D) Source #
It's like simple vradio
, but it can be controlled with external control.
The first argument is for external control.