Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GUI (Graphical User Interface) elements are handy to change the parameters of the sound in real time. It includes sliders, knobs, rollers, buttons and other widgets.
A GUI element consists of two parts. They are view (how it looks) and logic (what's going on with it). For example a slider can be horizontal or vertical or green or yellow or small or big. It's the view of the slider. And a slider can produce a continuous signal within the given interval. It's a logic of the slider.
Let's talk about the view. The view is divided on two parts:
- where element is placed or Layout.
- all other properties or just Properties.
The layout is defined with very simple functions. There are vertical and horizontal grouping of the elements. We can scale the element within the group and include an empty space in the group. Everything is aligned (see Csound.Gui.Layout). Other properties include colors, fonts (size and type), borders, specific properties of the widgets (see Csound.Gui.Props).
Let's consider the logic. The logic consists of three parts:
A widget can react on values, produce values or do something useful. There are special types of widgets:
Source
- they produce values onlySink
- they consume values onlyDisplay
- something is going on inside them (for example, it can show a "hello world" message)
Widgets can be simple and compound. Simple widgets are primitive elements (sliders, knobs, rollers, buttons). We have a special constructors that produce simple widgets (see Csound.Gui.Widget). Compound widgets glue together several widgets. That is the view contains several elements and all of them involved in the logic of the widget.
Synopsis
- data Gui
- type Widget a b = SE (Gui, Output a, Input b, Inner)
- type Input a = a
- type Output a = a -> SE ()
- type Inner = SE ()
- type Sink a = SE (Gui, Output a)
- type Source a = SE (Gui, Input a)
- type Display = SE Gui
- type SinkSource a = SE (Gui, Output a, Input a)
- widget :: SE (Gui, Output a, Input b, Inner) -> Widget a b
- sink :: SE (Gui, Output a) -> Sink a
- source :: SE (Gui, Input a) -> Source a
- display :: SE Gui -> Display
- sinkSource :: SE (Gui, Output a, Input a) -> SinkSource a
- sinkSlice :: SinkSource a -> Sink a
- sourceSlice :: SinkSource a -> Source a
- mapSource :: (a -> b) -> Source a -> Source b
- mapGuiSource :: (Gui -> Gui) -> Source a -> Source a
- mhor :: Monoid a => [Source a] -> Source a
- mver :: Monoid a => [Source a] -> Source a
- msca :: Double -> Source a -> Source a
- joinSource :: Source (SE a) -> Source a
- fromSource :: Source a -> SE a
- fromSourceSE :: Source (SE a) -> SE a
- resizeSource :: (Double, Double) -> Source a -> Source a
- panel :: Gui -> SE ()
- win :: Text -> (Int, Int) -> Gui -> SE ()
- panels :: [Gui] -> SE ()
- panelBy :: Text -> Maybe Rect -> Gui -> SE ()
- keyPanel :: Gui -> SE ()
- keyWin :: Text -> (Int, Int) -> Gui -> SE ()
- keyPanels :: [Gui] -> SE ()
- keyPanelBy :: Text -> Maybe Rect -> Gui -> SE ()
- module Csound.Control.Gui.Layout
- data Rect = Rect {}
- data Prop
- = SetLabel Text
- | SetMaterial Material
- | SetBoxType BoxType
- | SetColor1 Color
- | SetColor2 Color
- | SetTextColor Color
- | SetFontSize Int
- | SetFontType FontType
- | SetEmphasis Emphasis
- | SetSliderType SliderType
- | SetTextType TextType
- | SetButtonType ButtonType
- | SetOrient Orient
- | SetKnobType KnobType
- | SetLabelType LabelType
- data BorderType
- data Material
- data Emphasis
- = NoEmphasis
- | Italic
- | Bold
- | BoldItalic
- data FontType
- data Orient
- type Color = Colour Double
- forceProps :: [Prop] -> Gui -> Gui
- setBorder :: BorderType -> Gui -> Gui
- setLabel :: Text -> Gui -> Gui
- setMaterial :: Material -> Gui -> Gui
- setColor1 :: Color -> Gui -> Gui
- setColor2 :: Color -> Gui -> Gui
- setColors :: Color -> Color -> Gui -> Gui
- setTextColor :: Color -> Gui -> Gui
- setFontSize :: Int -> Gui -> Gui
- setFontType :: FontType -> Gui -> Gui
- setEmphasis :: Emphasis -> Gui -> Gui
- setOrient :: Orient -> Gui -> Gui
- module Csound.Control.Gui.Widget
- hlifts :: ([a] -> b) -> [Source a] -> Source b
- vlifts :: ([a] -> b) -> [Source a] -> Source b
- gridLifts :: Int -> ([a] -> b) -> [Source a] -> Source b
- lift1 :: (a -> b) -> Source a -> Source b
- hlift2 :: (a -> b -> c) -> Source a -> Source b -> Source c
- vlift2 :: (a -> b -> c) -> Source a -> Source b -> Source c
- hlift3 :: (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d
- vlift3 :: (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d
- hlift4 :: (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e
- vlift4 :: (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e
- hlift5 :: (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b
- vlift5 :: (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b
- hlifts' :: [Double] -> ([a] -> b) -> [Source a] -> Source b
- vlifts' :: [Double] -> ([a] -> b) -> [Source a] -> Source b
- hlift2' :: Double -> Double -> (a -> b -> c) -> Source a -> Source b -> Source c
- vlift2' :: Double -> Double -> (a -> b -> c) -> Source a -> Source b -> Source c
- hlift3' :: Double -> Double -> Double -> (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d
- vlift3' :: Double -> Double -> Double -> (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d
- hlift4' :: Double -> Double -> Double -> Double -> (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e
- vlift4' :: Double -> Double -> Double -> Double -> (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e
- hlift5' :: Double -> Double -> Double -> Double -> Double -> (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b
- vlift5' :: Double -> Double -> Double -> Double -> Double -> (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b
- hbind :: Source a -> (a -> Source b) -> Source b
- vbind :: Source a -> (a -> Source b) -> Source b
- happly :: (a -> Source b) -> Source a -> Source b
- vapply :: (a -> Source b) -> Source a -> Source b
- hmapM :: (a -> Source b) -> [a] -> Source [b]
- vmapM :: (a -> Source b) -> [a] -> Source [b]
- hbind' :: Double -> Double -> Source a -> (a -> Source b) -> Source b
- vbind' :: Double -> Double -> Source a -> (a -> Source b) -> Source b
- happly' :: Double -> Double -> (a -> Source b) -> Source a -> Source b
- vapply' :: Double -> Double -> (a -> Source b) -> Source a -> Source b
- hmapM' :: [Double] -> (a -> Source b) -> [a] -> Source [b]
- vmapM' :: [Double] -> (a -> Source b) -> [a] -> Source [b]
- gridMapM :: Int -> (a -> Source b) -> [a] -> Source [b]
Gui
A visual representation of the GUI-element.
Instances
At Sig2 Sig2 a => At Sig2 Sig2 (Source a) Source # | |
At Sig (SE Sig) a => At Sig (SE Sig) (Source a) Source # | |
At Sig2 (SE Sig2) a => At Sig2 (SE Sig2) (Source a) Source # | |
RenderCsd (Source (SE ())) Source # | |
Sigs a => RenderCsd (Source (SE a)) Source # | |
RenderCsd (Source ()) Source # | |
Sigs a => RenderCsd (Source a) Source # | |
SigSpace a => SigSpace (Source a) Source # | |
Sigs a => RenderCsd (a -> Source (SE Sig2)) Source # | |
(Sigs a, Sigs b) => RenderCsd (a -> Source (SE b)) Source # | |
(Sigs a, Sigs b) => RenderCsd (a -> Source b) Source # | |
type AtOut Sig2 Sig2 (Source a) Source # | |
type AtOut Sig (SE Sig) (Source a) Source # | |
type AtOut Sig2 (SE Sig2) (Source a) Source # | |
type Widget a b = SE (Gui, Output a, Input b, Inner) #
A widget consists of visible element (Gui), value consumer (Output) and producer (Input) and an inner state (Inner).
sinkSource :: SE (Gui, Output a, Input a) -> SinkSource a #
sinkSlice :: SinkSource a -> Sink a #
sourceSlice :: SinkSource a -> Source a #
mapSource :: (a -> b) -> Source a -> Source b #
A handy function for transforming the value of producers.
mapGuiSource :: (Gui -> Gui) -> Source a -> Source a #
A handy function for transforming the GUIs of producers.
mhor :: Monoid a => [Source a] -> Source a #
Horizontal grouping of widgets that can produce monoidal values.
mver :: Monoid a => [Source a] -> Source a #
Vertical grouping of widgets that can produce monoidal values.
fromSource :: Source a -> SE a Source #
resizeSource :: (Double, Double) -> Source a -> Source a Source #
Resizes all default minimal sizes for all elements in the source. It affects the total sizes of the widgets. So for example if our UI is too big and it doesn't fir to the screen we can make it smaller by scaling:
resizeSource (0.75, 0.5) uiSource
Panels
Renders the GUI elements on the window. Rectangle is calculated automatically (window doesn't listens for keyboard events).
win :: Text -> (Int, Int) -> Gui -> SE () Source #
Creates a window with the given name, size and content
win name (width, height) gui
panelBy :: Text -> Maybe Rect -> Gui -> SE () #
Renders the GUI elements on the window. We can specify the window title and rectangle of the window.
Renders the GUI elements on the window. Rectangle is calculated automatically (window listens for keyboard events).
keyPanelBy :: Text -> Maybe Rect -> Gui -> SE () #
Renders the GUI elements on the window. We can specify the window title and rectangle of the window. Panesls are sensitive to keyboard events.
Re-exports
module Csound.Control.Gui.Layout
A rectangle.
Properties of the widgets.
data BorderType #
Instances
Enum BorderType | |
Defined in Csound.Typed.Gui.Types succ :: BorderType -> BorderType # pred :: BorderType -> BorderType # toEnum :: Int -> BorderType # fromEnum :: BorderType -> Int # enumFrom :: BorderType -> [BorderType] # enumFromThen :: BorderType -> BorderType -> [BorderType] # enumFromTo :: BorderType -> BorderType -> [BorderType] # enumFromThenTo :: BorderType -> BorderType -> BorderType -> [BorderType] # |
The type of the material of the element. It affects sliders and buttons.
The orientation of the widget (slider, roller). This property is never needs to be set in practice. If this property is not set then default orientation is calculated from the bounding box of the widget. If the width is greater than the height then we need to use a horizontal widget otherwise it should be a vertical one.
forceProps :: [Prop] -> Gui -> Gui #
Sets the properties for a GUI element on all levels.
setBorder :: BorderType -> Gui -> Gui #
setMaterial :: Material -> Gui -> Gui #
setTextColor :: Color -> Gui -> Gui #
setFontSize :: Int -> Gui -> Gui #
setFontType :: FontType -> Gui -> Gui #
setEmphasis :: Emphasis -> Gui -> Gui #
module Csound.Control.Gui.Widget
Lifters
An easy way to combine visuals for sound sources.
hlifts :: ([a] -> b) -> [Source a] -> Source b Source #
Groups a list of Source-widgets. The visuals are horizontally aligned.
vlifts :: ([a] -> b) -> [Source a] -> Source b Source #
Groups a list of Source-widgets. The visuals are vertically aligned.
gridLifts :: Int -> ([a] -> b) -> [Source a] -> Source b Source #
Groups a list of Source-widgets. The visuals are put on the grid. The first argument is numer of elements i each row.
hlift2 :: (a -> b -> c) -> Source a -> Source b -> Source c Source #
Combines two sound sources. Visuals are aligned horizontally and the sound sources a grouped with the given function.
vlift2 :: (a -> b -> c) -> Source a -> Source b -> Source c Source #
Combines two sound sources. Visuals are aligned vertically and the sound sources a grouped with the given function.
hlift3 :: (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d Source #
The same as hlift2
but for three sound sources.
vlift3 :: (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d Source #
The same as vlift2
but for three sound sources.
hlift4 :: (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e Source #
The same as hlift2
but for four sound sources.
vlift4 :: (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e Source #
The same as vlift2
but for four sound sources.
hlift5 :: (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b Source #
The same as hlift2
but for five sound sources.
vlift5 :: (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b Source #
The same as vlift2
but for five sound sources.
Lifters with visual scaling
hlifts' :: [Double] -> ([a] -> b) -> [Source a] -> Source b Source #
Groups a list of Source-widgets. The visuals are horizontally aligned. It uses the list of proportions.
vlifts' :: [Double] -> ([a] -> b) -> [Source a] -> Source b Source #
Groups a list of Source-widgets. The visuals are vertically aligned. It uses the list of proportions.
hlift2' :: Double -> Double -> (a -> b -> c) -> Source a -> Source b -> Source c Source #
It's just like the hlift2
but two more parameters change visual scaling of the widgets.
vlift2' :: Double -> Double -> (a -> b -> c) -> Source a -> Source b -> Source c Source #
It's just like the vlift2
but two more parameters change visual scaling of the widgets.
hlift3' :: Double -> Double -> Double -> (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d Source #
The same as hlift2'
but for three sound sources.
vlift3' :: Double -> Double -> Double -> (a -> b -> c -> d) -> Source a -> Source b -> Source c -> Source d Source #
The same as vlift2'
but for three sound sources.
hlift4' :: Double -> Double -> Double -> Double -> (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e Source #
The same as hlift2'
but for four sound sources.
vlift4' :: Double -> Double -> Double -> Double -> (a -> b -> c -> d -> e) -> Source a -> Source b -> Source c -> Source d -> Source e Source #
The same as vlift2'
but for four sound sources.
hlift5' :: Double -> Double -> Double -> Double -> Double -> (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b Source #
The same as hlift2'
but for five sound sources.
vlift5' :: Double -> Double -> Double -> Double -> Double -> (a1 -> a2 -> a3 -> a4 -> a5 -> b) -> Source a1 -> Source a2 -> Source a3 -> Source a4 -> Source a5 -> Source b Source #
The same as vlift2'
but for five sound sources.
Monadic binds
hbind :: Source a -> (a -> Source b) -> Source b Source #
Monadic bind with horizontal concatenation of visuals.
vbind :: Source a -> (a -> Source b) -> Source b Source #
Monadic bind with vertical concatenation of visuals.
happly :: (a -> Source b) -> Source a -> Source b Source #
Monadic apply with horizontal concatenation of visuals.
vapply :: (a -> Source b) -> Source a -> Source b Source #
Monadic apply with vertical concatenation of visuals.
hmapM :: (a -> Source b) -> [a] -> Source [b] Source #
Creates a list of sources with mapping a function and stacks them horizontally.
vmapM :: (a -> Source b) -> [a] -> Source [b] Source #
Creates a list of sources with mapping a function and stacks them vertically.
hbind' :: Double -> Double -> Source a -> (a -> Source b) -> Source b Source #
Monadic bind with horizontal concatenation of visuals. It expects scaling factors for visuals as first two arguments.
vbind' :: Double -> Double -> Source a -> (a -> Source b) -> Source b Source #
Monadic bind with vertical concatenation of visuals. It expects scaling factors for visuals as first two arguments.
happly' :: Double -> Double -> (a -> Source b) -> Source a -> Source b Source #
Monadic apply with horizontal concatenation of visuals. It expects scaling factors for visuals as first two arguments.
vapply' :: Double -> Double -> (a -> Source b) -> Source a -> Source b Source #
Monadic apply with vertical concatenation of visuals. It expects scaling factors for visuals as first two arguments.
hmapM' :: [Double] -> (a -> Source b) -> [a] -> Source [b] Source #
It's like hmapM
but we can supply the list of relative sizes.
vmapM' :: [Double] -> (a -> Source b) -> [a] -> Source [b] Source #
It's like hvapM
but we can supply the list of relative sizes.
gridMapM :: Int -> (a -> Source b) -> [a] -> Source [b] Source #
Creates a list of sources with mapping a function and puts them on the grid. The first argument is the number of items in the row.