| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Typed.Spreadsheet
Description
The following program:
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE OverloadedStrings #-}
import Typed.Spreadsheet
main :: IO ()
main = textUI "Example program" $ do
a <- checkBox "a"
b <- spinButton "b" 1
c <- spinButton "c" 0.1
d <- entry "d"
return (display (a, b + c, d))... creates a user interface that looks like this:

Every time you update a control on the left panel, the right panel updates in response:

This library also supports graphical output, like in the following program:
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE OverloadedStrings #-}
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" $ do
color <- radioButton "Color" Red [Orange .. Purple]
r <- spinButtonAt 100 "Radius" 1
x <- spinButton "X Coordinate" 1
y <- spinButton "Y Coordinate" 1
return (circle r # fc (toColor color) # translate (r2 (x, y)))This produces a canvas that colors, resizes, and moves a circle in response to user input:

The general workflow for this library is:
- You build primitive
Updatablevalues usingcheckBox,spinButton,entry, orradioButton, each of which corresponds to a control on the left panel of the user interface - Combine
Updatablevalues usingApplicativeDonotation. Composite values update whenever one of their substituent values update - You consume an
(value usingUpdatableText)textUI, which displays the continuously updating value in the right panel of the user interface
You can get started quickly by cloning and building this project:
$ git clone https://github.com/Gabriel439/Haskell-Typed-Spreadsheet-Library.git $ stack build --install-ghc # Builds the executable $ stack exec typed-spreadsheet-example # Runs the executable
... or if you are using OS X, then build the project using:
$ stack --stack-yaml=osx.yaml build --install-ghc
That project includes the code for the above examples in the exec/
subdirectory. Just modify that file and rebuild to play with the example.
NOTE: You must compile your program with the -threaded flag. The example
project takes care of this.
See the "Examples" section at the bottom of this module for more examples.
- data Updatable a
- textUI :: Text -> Updatable Text -> IO ()
- cellUI :: Text -> Updatable [(Text, Text)] -> IO ()
- graphicalUI :: Text -> Updatable (Diagram Cairo) -> IO ()
- ui :: (HBox -> IO resource) -> (resource -> event -> IO ()) -> Text -> Updatable event -> IO ()
- checkBox :: Text -> Updatable Bool
- spinButton :: Text -> Double -> Updatable Double
- entry :: Text -> Updatable Text
- radioButton :: Show a => Text -> a -> [a] -> Updatable a
- checkBoxAt :: Bool -> Text -> Updatable Bool
- spinButtonAt :: Double -> Text -> Double -> Updatable Double
- hscale :: Text -> Double -> Updatable Double
- hscaleAt :: Double -> Text -> Double -> Updatable Double
- hscaleWithRange :: Double -> Double -> Double -> Text -> Double -> Updatable Double
- vscale :: Text -> Double -> Updatable Double
- vscaleAt :: Double -> Text -> Double -> Updatable Double
- vscaleWithRange :: Double -> Double -> Double -> Text -> Double -> Updatable Double
- entryAt :: Text -> Text -> Updatable Text
- display :: Show a => a -> Text
Types
An updatable input value
Build a Text-based user interface
Build a cell-based user interface
Build a Diagram-based user interface
Arguments
| :: (HBox -> IO resource) | Acquire initial resource |
| -> (resource -> event -> IO ()) | Callback function to process each event |
| -> Text | Window title |
| -> Updatable event | Event stream |
| -> IO () |
Underlying function for building custom user interfaces
Controls
Arguments
| :: Show a | |
| => Text | Label |
| -> a | 1st choice (Default selection) |
| -> [a] | Remaining choices |
| -> Updatable a |
A control that selects from one or more mutually exclusive choices
Controls with Defaults
Same as checkBox except that you can specify the initial state
Same as spinButton except that you can specify the initial state
A Double horizontal slider
Same as hscaleButton except that you can specify the initial state
Arguments
| :: Double | Minimum value |
| -> Double | Maximum value |
| -> Double | Initial state |
| -> Text | Label |
| -> Double | Step size |
| -> Updatable Double |
Same as hscaleButton except that you can specify the range and initial state
Same as vscaleButton except that you can specify the initial state
Arguments
| :: Double | Minimum value |
| -> Double | Maximum value |
| -> Double | Initial state |
| -> Text | Label |
| -> Double | Step size |
| -> Updatable Double |
Same as vscaleButton except that you can specify the range and initial state
Same as entry except that you can specify the initial state
Utilities
Examples
Mortgage calculator:
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE OverloadedStrings #-}
import Typed.Spreadsheet
main :: IO ()
main = textUI "Mortgage payment" $ do
mortgageAmount <- spinButton "Mortgage Amount" 1000
numberOfYears <- spinButton "Number of years" 1
yearlyInterestRate <- spinButton "Yearly interest rate (%)" 0.01
let n = truncate (numberOfYears * 12)
let i = yearlyInterestRate / 12 / 100
return ("Monthly payment: $" <> display (mortgageAmount * (i * (1 + i) ^ n) / ((1 + i) ^ n - 1)))Example input and output:

Mad libs:
{-# LANGUAGE OverloadedStrings #-}
import Typed.Spreadsheet
noun = entry "Noun"
verb = entry "Verb"
adjective = entry "Adjective"
example =
"I want to " <> verb <> " every " <> noun <> " because they are so " <> adjective
main :: IO ()
main = textUI "Mad libs" exampleThe above program works because the Updatable type implements IsString
and Monoid, so no Applicative operations are necessary
Example input and output:

Sinusoid plot:
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Prelude
import Typed.Spreadsheet
main :: IO ()
main = graphicalUI "Example program" $ do
amplitude <- spinButtonAt 50 "Amplitude (Pixels)" 0.1
frequency <- spinButtonAt 0.1 "Frequency (Pixels⁻¹)" 0.001
phase <- spinButtonAt 90 "Phase (Degrees)" 1
let axes = arrowBetween (p2 (0, 0)) (p2 ( 100, 0))
<> arrowBetween (p2 (0, 0)) (p2 (-100, 0))
<> arrowBetween (p2 (0, 0)) (p2 ( 0, 100))
<> arrowBetween (p2 (0, 0)) (p2 ( 0, -100))
let f x = amplitude * cos (frequency * x + phase * pi / 180)
let points = map (\x -> p2 (x, f x)) [-100, -99 .. 100]
return (strokeP (fromVertices points) <> axes)Example input and output:

Factor diagram:
{-# LANGUAGE OverloadedStrings #-}
import Diagrams.Prelude
import Diagrams.TwoD.Factorization (factorDiagram')
import Typed.Spreadsheet
main :: IO ()
main = graphicalUI "Factor diagram" $ do
x <- spinButtonAt 3 "Factor #1" 1
y <- spinButtonAt 3 "Factor #2" 1
z <- spinButtonAt 3 "Factor #3" 1
return (factorDiagram' [truncate x, truncate y, truncate z] # scale 10)Example input and output:
