I've added a diagrams
backend to my typed-spreadsheet
library which you can use to build composable graphical programs that update in response to user input.
Here's an example program that displays a circle that changes in response to various user inputs:
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Backend.Cairo (Cairo)
import Diagrams.Prelude
import Typed.Spreadsheet
data AColor = Red | Orange | Yellow | Green | Blue | Purple
deriving (Enum, Bounded, Show)
toColor :: AColor -> Colour Double
toColor Red = red
toColor Orange = orange
toColor Yellow = yellow
toColor Green = green
toColor Blue = blue
toColor Purple = purple
main :: IO ()
main = graphicalUI "Example program" logic
where
logic = combine <$> radioButton "Color" Red [Orange .. Purple]
<*> spinButtonAt 100 "Radius" 1
<*> spinButton "X Coordinate" 1
<*> spinButton "Y Coordinate" 1
combine :: AColor -> Double -> Double -> Double -> Diagram Cairo
combine color r x y =
circle r # fc (toColor color) # translate (r2 (x, -y))
Here is a video showing the example program in action:
Applicatives
The first half of the main
function (named logic
) requests four users inputs to parametrize the displayed circle:
- A radio button for selecting the circle's color
- A spin button for controlling radius which defaults to 100 (pixels)
- A spin button for controlling the x coordinate for the center of the circle
- A spin button for controlling the y coordinate for the center of the circle
Each of these inputs is an Updatable
value and we can express that using Haskell's type system:
radioButton "Color" Red [Orange .. Purple] :: Updatable AColor
spinButtonAt 100 "Radius" 1 :: Updatable Double
spinButton "X Coordinate" 1 :: Updatable Double
spinButton "Y Coordinate" 1 :: Updatable Double
The Updatable
type implements Haskell's Applicative
interface, meaning that you can combine smaller Updatable
values into larger Updatable
values using Applicative
operations.
For example, consider this pure function that consumes four pure inputs and produces a pure diagram:
combine
:: AColor
-> Double
-> Double
-> Double
-> Diagram Cairo
Normally if we compute a pure function we would write something like this:
combine Green 40 10 20
:: Diagram Cairo
However, this result is static and unchanging. I would like to transform this function into one that accepts Updatable
arguments and produces an Updatable
result.
Fortunately, Haskell's Applicative
interface lets us do just that. We can lift any pure function to operate on any type that implements the Applicative
interface like the Updatable
type. All we have to do is separate the function from the first argument using the (<$>)
operator and separate each subsequent argument using the (<*>)
operator:
combine <$> radioButton "Color" Red [Orange .. Purple]
<*> spinButtonAt 100 "Radius" 1
<*> spinButton "X Coordinate" 1
<*> spinButton "Y Coordinate" 1
:: Updatable (Diagram Cairo)
Now the combine
function accepts four Updatable
arguments and produces an Updatable
result! I can then pass this result to the graphicalUI
function which builds a user interface from any Updatable
Diagram
:
graphicalUI :: Text -> Updatable Diagram -> IO ()
main = graphicalUI "Example program" logic
The Applicative
operations ensure that every time one of our primitive Updatable
inputs change, the composite Updatable
Diagram
immediately reflects that change.
Charts
One reason I wanted diagrams
integration was to begin building interactive charts for typed spreadsheets. I'll illustrate this using a running example where I building up a successively more complex chart piece-by-piece.
Let's begin with a simple rectangle with an adjustable height (starting at 100 pixels):
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Backend.Cairo (Cairo)
import Diagrams.Prelude
import Typed.Spreadsheet
import qualified Data.Text as Text
bar :: Int -> Updatable (Diagram Cairo)
bar i = fmap buildRect (spinButtonAt 100 label 1)
where
buildRect height = alignB (rect 30 height)
label = "Bar #" <> Text.pack (show i)
main :: IO ()
main = graphicalUI "Example program" (bar 1)
When we run this example we get a boring chart with a single bar:
However, the beauty of Haskell is composable abstractions like Applicative
. We can take smaller pieces and very easily combine them into larger pieces. Each piece does one thing and does it well, and we compose them to build larger functionality from sound building blocks.
For example, if I want to create a bar chart with five individually updatable bars, I only need to add a few lines of code to create five bars and connect them:
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Backend.Cairo (Cairo)
import Diagrams.Prelude
import Typed.Spreadsheet
import qualified Data.Text as Text
bar :: Int -> Updatable (Diagram Cairo)
bar i = fmap buildRect (spinButtonAt 100 label 1)
where
buildRect height = alignB (rect 30 height)
label = "Bar #" <> Text.pack (show i)
bars :: Int -> Updatable (Diagram Cairo)
bars n = fmap combine (traverse bar [1..n])
where
combine bars = alignX 0 (hcat bars)
main :: IO ()
main = graphicalUI "Example program" (bars 5)
This not only creates a bar chart with five bars, but also auto-generates a corresponding input cell for each bar:
Even better, all the inputs are strongly typed! The program enforces that all inputs are well-formed and won't let us input non-numeric values.
We also benefit from all the features of Haskell's diagrams
library, which is an powerful Haskell library for building diagrams. Let's spruce up the diagram a little bit by adding color, spacing, and other embellishments:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Backend.Cairo (Cairo)
import Diagrams.Prelude
import Typed.Spreadsheet
import qualified Data.Text as Text
bar :: Int -> Updatable (Diagram Cairo)
bar i = fmap buildBar (spinButtonAt 100 label 0.2)
where
color = case i `mod` 3 of
0 -> red
1 -> green
2 -> yellow
buildBar height =
( alignB ( vine
<> bubbles
)
<> alignB ( roundedRect 25 (height - 5) 5 # fc white
<> roundedRect 30 height 5 # fc color
)
)
where
stepSize = 15
vine = strokeP (fromVertices (map toPoint [0..height]))
where
toPoint n = p2 (5 * cos (pi * n / stepSize), n)
bubble n =
circle radius
# translate (r2 (0, n * stepSize))
# fc lightblue
where
radius = max 1 (min stepSize (height - n * stepSize)) / 5
bubbles = foldMap bubble [1 .. (height / stepSize) - 1]
label = "Bar #" <> Text.pack (show i)
bars :: Int -> Updatable (Diagram Cairo)
bars n = fmap combine (traverse bar [1..n])
where
combine bars = alignX 0 (hsep 5 [alignL yAxis, alignL (hsep 5 bars)])
yAxis = arrowV (r2 (0, 150))
main :: IO ()
main = graphicalUI "Example program" (bars 5)
One embellishment is a little animation where bubbles fade in and out near the top of the bar:
We can customize the visuals to our heart's content becuse the spreadsheet and diagram logic are both embedded within a fully featured programming language.
Conclusion
The typed-spreadsheet
library illustrates how you can use the Haskell language to build high-level APIs that abstract way low-level details such as form building or reactive updates in this case.
In many languages high-level abstractions come at a price: you typically have to learn a domain-specific language in order to take advantage of high-level features. However, Haskell provides reusable interfaces like Applicative
s that you learn once and apply over and over and over to each new library that you learn. This makes the Haskell learning curve very much like a "plateau": initially steep as you learn the reusable interfaces but then very flat as you repeatedly apply those interfaces in many diverse domains.
If you would like contribute to the typed-spreadsheet
library you can contribute out-of-the-box charting functionality to help the library achieve feature parity with real spreadsheet software.
You can learn more about the library by checking out:
- the Github project
- the Hackage documentation
This is awesome.
ReplyDeleteThis looks really cool! I was wondering if you were planning on adding action buttons and perhaps a save-to-file feature? That way we could e.g. use the interactive features until we have a diagrams output we want, and then just hit the save-button to write it to a png or so.
ReplyDeleteYes, but first I would like to port this to work in the browser via GHCJS so that it's easier for people to install and distribute the result to others.
DeleteThis is really great! I love the design of typed-spreadsheet. It inspired me to create a Purescript version which can be used to create reactive web interfaces: https://github.com/sharkdp/purescript-flare Thanks!
ReplyDelete