Euterpea-1.0.0: Library for computer music research and education

Safe HaskellNone

Euterpea.IO.MUI

Documentation

data UISF b c

Instances

Category UISF 
ArrowLoop UISF 
ArrowChoice UISF 
Arrow UISF 
ArrowInit UISF 
ArrowCircuit UISF 
ArrowTime UISF 
ArrowIO UISF 

asyncV :: (ArrowIO a, NFData c) => Double -> DeltaT -> (ThreadId -> a () ()) -> Automaton (->) b c -> a (b, Time) [(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

data UIParams

Constructors

UIParams 

Fields

uiInitialize :: IO ()
 
uiClose :: IO ()
 
uiTitle :: String
 
uiSize :: Dimension
 
uiInitFlow :: Flow
 
uiTickDelay :: Double
 

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

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

label :: String -> UISF a a

displayStr :: UISF String ()

display :: Show a => UISF a ()

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

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

textbox :: UISF String String

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

button :: String -> UISF () Bool

stickyButton :: String -> UISF () Bool

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

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

radio :: [String] -> 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 -> Time -> Color -> UISF [(a, Time)] ()

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

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

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

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

data LayoutType

Constructors

Stretchy 

Fields

minSize :: Int
 
Fixed 

Fields

fixedSize :: Int
 

data Color

Constructors

Black 
Blue 
Green 
Cyan 
Red 
Magenta 
Yellow 
White 

Instances

Bounded Color 
Enum Color 
Eq Color 
Ord Color 
Read Color 
Show Color 
Ix Color