csound-expression-5.0.1: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Control.Gui.Widget

Contents

Description

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.

Synopsis

Common properties

data ValDiap :: *

The diapason of the continuous value.

Constructors

ValDiap 

data ValScaleType :: *

Constructors

Linear 
Exponential 

data ValSpan :: *

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

uspan :: ValSpan

Unit span. A special case:

uspan = linSpan 0 1

bspan :: ValSpan

Bipolar unit span. A special case:

uspan = linSpan (-1) 1

uspanExp :: ValSpan

An exponential unit span. A special case:

uspan = expSpan 0 1

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 

doc: http://www.csounds.com/manual/html/FLcount.html

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) 

doc: http://www.csounds.com/manual/html/FLjoy.html

knob :: String -> ValSpan -> Double -> Source Sig

A FLTK widget opcode that creates a knob.

knob valueSpan initValue

doc: http://www.csounds.com/manual/html/FLknob.html

data KnobType :: *

Constructors

ThreeD (Maybe Int) 
Pie 
Clock 
Flat 

Instances

roller :: String -> ValSpan -> ValStep -> Double -> Source Sig

FLroller is a sort of knob, but put transversally.

roller valueSpan step initVal

doc: http://www.csounds.com/manual/html/FLroller.html

slider :: String -> ValSpan -> Double -> Source Sig

FLslider puts a slider into the corresponding container.

slider valueSpan initVal 

doc: http://www.csounds.com/manual/html/FLslider.html

sliderBank :: String -> [Double] -> Source [Sig]

Constructs a list of linear unit sliders (ranges in [0, 1]). It takes a list of init values.

data SliderType :: *

Constructors

Fill 
Engraved 
Nice 

Instances

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 

doc: http://www.csounds.com/manual/html/FLtext.html

data TextType :: *

Constructors

NormalText 
NoDrag 
NoEdit 

Instances

Other widgets

box :: String -> Display

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

doc: http://www.csounds.com/manual/html/FLbox.html

button :: String -> Source (Evt Unit)

A FLTK widget opcode that creates a button.

button text

doc: http://www.csounds.com/manual/html/FLbutton.html

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).

Instances

toggle :: String -> Bool -> Source (Evt D)

A FLTK widget opcode that creates a toggle button.

button text

doc: http://www.csounds.com/manual/html/FLbutton.html

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

doc: http://www.csounds.com/manual/html/FLbutBank.html

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

doc: http://www.csounds.com/manual/html/FLbutBank.html

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

Transformers

setTitle :: String -> Gui -> SE Gui

Appends a title to a group of widgets.

Keyboard

data KeyEvt :: *

Keyboard events.

Constructors

Press Key 
Release Key 

Instances

keyIn :: KeyEvt -> Evt Unit

The stream of keyboard press/release events.

charOn :: Char -> Evt Unit Source

Shortcut for press CharKey events.

charOff :: Char -> Evt Unit Source

Shortcut for release CharKey events.

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.

ujoy :: (Double, Double) -> Source (Sig, Sig) Source

Unit linear joystick.

hradio :: [String] -> Int -> Source (Evt D) Source

Horizontal radio group.

vradio :: [String] -> Int -> Source (Evt D) Source

Vertical radio group.

hradioSig :: [String] -> Int -> Source Sig Source

Horizontal radio group.

vradioSig :: [String] -> Int -> Source Sig Source

Vertical radio group.

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

type Range a = (a, a) Source

Pair of minimum and maximum values.

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.

hradioSig' :: Sig -> [String] -> Int -> Source Sig Source

It's like simple hradioSig, but it can be controlled with external control. The first argument is for external control.

vradioSig' :: Sig -> [String] -> Int -> Source Sig Source

It's like simple vradioSig, but it can be controlled with external control. The first argument is for external control.