| Safe Haskell | None |
|---|
Typed.Spreadsheet
Description
The following program:
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Typed.Spreadsheet
main :: IO ()
main = textUI "Example program" logic
where
logic = combine <$> checkBox "a"
<*> spinButton "b" 1
<*> spinButton "c" 0.1
<*> entry "d"
combine a b c d = 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:
Once ghc-8.0 is out then you can simplify the above program even further
using the ApplicativeDo extension:
{-# 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)) )
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 * You transform or combineUpdatablevalues usingFunctorandApplicativeoperations. 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
That project includes the code for the above example in exec/Main.hs. 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.
Types
An updatable input value
Build a Text-based user interface
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
Utilities
Examples
Mortgage calculator:
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Data.Monoid
import Data.Text (Text)
import Typed.Spreadsheet
payment :: Double -> Double -> Double -> Text
payment mortgageAmount numberOfYears yearlyInterestRate
= "Monthly payment: $"
<> display (mortgageAmount * (i * (1 + i) ^ n) / ((1 + i) ^ n - 1))
where
n = truncate (numberOfYears * 12)
i = yearlyInterestRate / 12 / 100
logic :: Updatable Text
logic = payment <$> spinButton "Mortgage Amount" 1000
<*> spinButton "Number of years" 1
<*> spinButton "Yearly interest rate (%)" 0.01
main :: IO ()
main = textUI "Mortgage payment" logic
Example input and output:
Mad libs:
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid
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" example
The above program works because the Updatable type implements IsString
and Monoid, so no Applicative operations are necessary
Example input and output: