| Safe Haskell | Safe-Inferred |
|---|
MVC.Updates
Contents
Description
Use this library to build mvc applications that consume many individually
Updatable values, such as:
- spread sheets,
- control panels, and:
- data visualizations.
This library builds on top of the mvc library, so you may want to read
the documentation in the MVC module if you haven't already.
Here is an example program to illustrate how this library works:
import Control.Applicative ((<$>), (<*>))
import Control.Foldl (last, length)
import MVC
import MVC.Updates
import MVC.Prelude (stdinLines, tick)
import qualified Pipes.Prelude as Pipes
import Prelude hiding (last, length)
data Example = Example (Maybe String) Int deriving (Show)
lastLine :: Updatable (Maybe String)
lastLine = On last stdinLines
seconds :: Updatable Int
seconds = On length (tick 1.0)
example :: Updatable Example
example = Example <$> lastLine <*> seconds
viewController :: Managed (View Example, Controller Example)
viewController = do
controller <- updates Unbounded example
return (asSink print, controller)
model :: Model () Example Example
model = asPipe $ Pipes.takeWhile (\(Example str _) -> str /= Just "quit")
main :: IO ()
main = runMVC () model viewController
First we build two simple Updatable values:
-
lastLineupdates every time the user enters a new line at standard input -
secondsincrements every second
Then we assemble them into a derived Updatable value using Applicative
operations. This derived value updates every time one of the two primitive
values updates:
$ ./example Example Nothing 0 Test<Enter> Example (Just "Test") 0 Example (Just "Test") 1 Example (Just "Test") 2 ABC<Enter> Example (Just "ABC") 2 Example (Just "ABC") 3 quit<Enter> $
Every time the user types in a new line of input the controller emits a
new Example value that overrides the first field. Similarly, every time
one second passes the controller emits a new Example value that
overrides the second field.
The Example section at the bottom of this module contains an extended example for how to build a GTK-based spreadsheet using this library.
- data Updatable a = forall e . On (Fold e a) (Managed (Controller e))
- updates :: Buffer a -> Updatable a -> Managed (Controller a)
- module Control.Foldl
Updates
You can combine smaller updates into larger updates using Applicative
operations:
_As :: Updatable A _Bs :: Updatable B _ABs :: Updatable (A, B) _ABs = liftA2 (,) _As _Bs
_ABs updates every time either _As updates or _Bs updates, caching and
reusing values that do not update. For example, if _As emits a new A,
then _ABs reuses the old value for B. Vice versa, if _Bs emits a new
B then _ABs reuses the old value for A.
This caching behavior transitively works for any number of updates that you
combine using Applicative operations. Also, the internal code is
efficient and only introduces one extra thread no matter how many updates
you combine. You can even skip the extra thread if you unpack the Fold
type and use the fields directly within your mvc program. Study the
source code for updates to see this in action.
Tip: To efficiently merge a large number of updates, store them in a
Seq and use sequenceA to merge them:
sequenceA :: Seq (Updatable a) -> Updatable (Seq a)
A concurrent, updatable value
Constructors
| forall e . On (Fold e a) (Managed (Controller e)) |
Instances
updates :: Buffer a -> Updatable a -> Managed (Controller a)Source
Convert an Updatable value to a Managed Controller that emits updates
You must specify how to Buffer the updates
Example
The following example program shows how to build a spreadsheet with input and
output cells using the gtk, mvc and mvc-updates libraries.
The first half of the program contains all the gtk-specific logic. The
key function is spreadsheet, which returns high-level commands to build
multiple input and output cells.
-- This must be compiled with the `-threaded` flag
{-# LANGUAGE TemplateHaskell #-}
import Control.Applicative (Applicative, (<$>), (<*>))
import Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
import Control.Concurrent.Async (async, wait)
import Control.Foldl (lastDef)
import Graphics.UI.Gtk
import Lens.Family.TH (makeLenses)
import MVC
import MVC.Updates
makeInCell :: VBox -> Updatable Double
makeInCell vBox = On (lastDef 0) $ managed $ \k -> do
(output, input) <- spawn Unbounded
spinButton <- spinButtonNewWithRange 0 100 1
onValueSpinned spinButton $ do
n <- get spinButton spinButtonValue
_ <- atomically (send output n)
return ()
boxPackStartDefaults vBox spinButton
widgetShowAll vBox
k (asInput input)
makeOutCell :: VBox -> Managed (View Double)
makeOutCell vBox = liftIO $ do
entry <- entryNew
boxPackStartDefaults vBox entry
return $ asSink $ \n -> postGUISync $ entrySetText entry (show n)
spreadsheet :: Managed (Updatable Double, Managed (View Double), IO ())
spreadsheet = managed $ \k -> do
initGUI
window <- windowNew
hBox <- hBoxNew False 0
vBoxL <- vBoxNew False 0
vBoxR <- vBoxNew False 0
set window [windowTitle := "Spreadsheet", containerChild := hBox]
boxPackStartDefaults hBox vBoxL
boxPackStartDefaults hBox vBoxR
mvar <- newEmptyMVar
a <- async $ k (makeInCell vBoxL, makeOutCell vBoxR, putMVar mvar ())
takeMVar mvar
on window deleteEvent $ do
liftIO mainQuit
return False
widgetShowAll window
mainGUI
wait a
Input cells are Updatable values, and output cells are Managed
Views. Since Updatable values are Applicatives, we can combine
input cells into a single Updatable value (represented by the In
type) that updates whenever any individual cell updates:
data Out = O { _o1 :: Double, _o2 :: Double, _o3 :: Double, _o4 :: Double }
data In = I { _i1 :: Double, _i2 :: Double, _i3 :: Double, _i4 :: Double }
makeLenses ''Out
o1, o2, o3, o4 :: Functor f => (Double -> f Double) -> Out -> f Out
model :: Model () In Out
model = asPipe $ loop $ \(I i1 i2 i3 i4) -> do
return $ O (i1 + i2) (i2 * i3) (i3 - i4) (max i4 i1)
main :: IO ()
main = runMVC () model $ do
(inCell, outCell, go) <- spreadsheet
c <- updates Unbounded $ I <$> inCell <*> inCell <*> inCell <*> inCell
v <- fmap (handles o1) outCell
<> fmap (handles o2) outCell
<> fmap (handles o3) outCell
<> fmap (handles o4) outCell
liftIO go
return (v, c)
-- This must be compiled with the `-threaded` flag
The model contains the pure fragment of our program that relates input
cells to output cells. In this example, each output cell is a function
of two input cells.
If you compile and run the above program with the -threaded flag, a
small spread sheet window will open with input cells on the left-hand
side and output cells on the right-hand side. Modifying any input cell
will automatically update all output cells.
Re-exports
Control.Foldl re-exports the Fold type
module Control.Foldl