typed-spreadsheet-1.1.0: Typed and composable spreadsheets

Safe HaskellNone

Typed.Spreadsheet

Contents

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)) )

This library also supports graphical output, like in the following program:

 {-# 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))

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 Updatable values using checkBox, spinButton, entry, or radioButton, each of which corresponds to a control on the left panel of the user interface * You transform or combine Updatable values using Functor and Applicative operations. Composite values update whenever one of their substituent values update * You consume an (Updatable Text) value using 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.

Synopsis

Types

data Updatable a Source

An updatable input value

textUISource

Arguments

:: Text

Window title

-> Updatable Text

Program logic

-> IO () 

Build a Text-based user interface

graphicalUISource

Arguments

:: Text

Window title

-> Updatable (Diagram Cairo)

Program logic

-> IO () 

Build a Diagram-based user interface

Controls

checkBoxSource

Arguments

:: Text

Label

-> Updatable Bool 

A check box that returns True if selected and False if unselected

spinButtonSource

Arguments

:: Text

Label

-> Double

Step size

-> Updatable Double 

A Double spin button

entrySource

Arguments

:: Text

Label

-> Updatable Text 

A Text entry

radioButtonSource

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

checkBoxAtSource

Arguments

:: Bool

Initial state

-> Text

Label

-> Updatable Bool 

Same as checkBox except that you can specify the initial state

spinButtonAtSource

Arguments

:: Double

Initial state

-> Text

Label

-> Double

Step size

-> Updatable Double 

Same as spinButton except that you can specify the initial state

entryAtSource

Arguments

:: Text

Initial state

-> Text

Label

-> Updatable Text 

Same as entry except that you can specify the initial state

Utilities

display :: Show a => a -> TextSource

Convert a Showable value to Text

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:

Sinusoid plot:

 {-# LANGUAGE OverloadedStrings #-}
 
 import Diagrams.Backend.Cairo (Cairo)
 import Diagrams.Prelude
 import Typed.Spreadsheet
 
 main :: IO ()
 main = graphicalUI "Example program" logic
   where
     logic = combine <$> spinButtonAt 50  "Amplitude (Pixels)"   0.1
                     <*> spinButtonAt 0.1 "Frequency (Pixels⁻¹)" 0.001                     <*> spinButtonAt 90  "Phase (Degrees)"      1
 
     combine :: Double -> Double -> Double -> Diagram Cairo
     combine amplitude frequency phase = strokeP (fromVertices points) <> axes
       where
         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))
 
         f x = amplitude * cos (frequency * x + phase * pi / 180)
 
         points = map (\x -> p2 (x, f x)) [-100, -99 .. 100]

Example input and output:

Factor diagram:

 {-# LANGUAGE OverloadedStrings #-}
 
 import Diagrams.Backend.Cairo (Cairo)
 import Diagrams.Prelude
 import Diagrams.TwoD.Factorization (factorDiagram')
 import Typed.Spreadsheet
 
 main :: IO ()
 main = graphicalUI "Factor diagram" logic
   where
     logic = combine <$> spinButtonAt 3 "Factor #1" 1
                     <*> spinButtonAt 3 "Factor #2" 1
                     <*> spinButtonAt 3 "Factor #3" 1
 
     combine :: Double -> Double -> Double -> Diagram Cairo
     combine x y z =
         factorDiagram' [truncate x, truncate y, truncate z] # scale 10

Example input and output: