Haskell in web browser/Calc example

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Conclusion: all together

In conclusion, let's finally develop a program that does something useful. As another "classical" example, this will be a RPN calculator.

-- Begin Pasteable Code --
module TutEx6 where

import CPS
import Data.Char
import Graphics.UI.HsWTK
import DOM.Level2.Event
import DOM.Level2.Events
import DOM.Level2.KeyEvent
import DOM.Level2.HTMLDivElement
import DOM.Level2.HTMLSpanElement
import Control.Concurrent.JSThreads

main = docBodyC mainW

mainW = msgBox $ \calcmb ->
        msgBox $ \dispmb ->
        mkDiv `withStyle` ["border" := "1px solid black"
                          ,"width"  := "200px"
                          ,"height" := "150px"
                          ,"text-align" := "center"]
          |<< (mkDiv `withStyle` ["height" := "20%"
                                 ,"text-align" := "right"
                                 ,"vertical-align" := "middle"
                                 ,"overflow" := "hidden"]
                 |<< (textP "\160" +++ textP "\160"
                  +++ active (updMapA "0" id dispmb))
           +++ foldr (+++) nowidget (map (cbtn calcmb) btxt)
           +++ active (passMapStateA ci calc (show . acc) calcmb dispmb)
           +++ active (evtBCastA "keydown" clkey [calcmb])
           +++ active (tabIndexA 0))

clkey :: TKeyEvent -> CPS Bool Char

clkey e k = preventDefault e $ \_ -> get'keyCode e $ \c -> k $ case c of
  38 -> '^'
  107 -> '+'
  61 -> '+'
  109 -> '-'
  106 -> '*'
  191 -> '/'
  111 -> '/'
  59 -> '/'
  _ -> chr c

data CalcST = CalcST {acc :: Int, stack :: [Int], rst :: Int}

ci = CalcST {acc = 0, stack = [], rst = 0}

calc :: CalcST -> Char -> CalcST

calc st c = case c of
  'C' -> ci
  d | isDigit d -> let acc' = rst st * acc st * 10 + ord d - ord '0' 
                   in  st {acc = acc', rst = 1}
  '^' -> st {rst = 0, stack = (acc st) : (stack st)}
  o | o `elem` ['+', '-', '*', '/'] -> 
      let op '+' = (+)
          op '-' = (-)
          op '*' = (*)
          op '/' = div
      in  if null (stack st) 
            then st
            else  let acc' = op o (head $ stack st) (acc st)
                  in  st {rst = 0, 
                          stack = acc' : tail (stack st), 
                          acc = acc'}
  _   -> st

btxt = ['1', '2', '3', '+',
        '4', '5', '6', '-',
        '7', '8', '9', '*',
        'C', '0', '^', '/']

cbtn mb txt = mkDiv `withStyle` ["float" := "left"
                                ,"width" := "25%"
                                ,"height" := "20%"
                                ,"margin" := "0px"
                                ,"vertical-align" := "middle"
                                ,"text-align" := "center"]
                |<< buttonI `withStyle` ["width" := "80%"
                                        ,"height" := "80%"
                                        ,"font-size" := "80%"] 
                      |<< (textP [txt]
                       +++ active (evtBCastA "click" (evt2ConstU txt) [mb]))

-- End   Pasteable Code --

The main Widget, mainW consists of the following pieces:

  • Two Message Boxes. One (calcmb) will be used to transmit keystrokes and mouse clicks received from the browser's input facilities. Another (dispmb) will be used to update the calculator's display element.
  • A <DIV> element with visible border: it encloses all other elements of the calculator. It is also responsible for receiving keyboard input.

The following elements are nested within the above mentioned <DIV>:

  • A <DIV> element that contains the calculator's display.
  • 16 buttons for mouse input. Note the use of foldr and map. All buttons use the same Message Box calcmb, so it is passed to each button's creation function. Each button uses its own character taken from the btxt list: button creation function is mapped over this list. Finally, the resulting list is folded with +++ to sequence all buttons properly.
  • Activator which implements the internal (stateful) logic of the calculator. It is based on passMapStateA which receives messages from its input Message Box, maintains internal state transitions based on what is received, and maps internal state to messages sent to the output Message Box. That's how the two parts (user input and result display) are wired together.
  • Activator based on evtBCastA to catch keystrokes and route them to the same Message Box where mouse clicks go.
  • Activator based on tabIndexA. Although DOM does not define the tabIndex property for most HTML elements, according to this (last comment), it is necessary to initialize this property in order to be able to receive keystrokes on <DIV> elements.

The clkey function performs proper mapping of keystrokes to simulate mouse clicks on buttons. It extracts the value of keyCode property from the event received, and remaps certain codes, finally passing a character to the continuation.

The CalcST defines the internal state of the calculator. It includes the accumulator (where the user input goes), the stack (a list of numbers), and the reset flag which helps update the display properly when entry of a new number begins.

Internal logic of the calculator (calc) is pretty straighforward: numbers typed in are pushed down the stack when "^" button is clicked, or the "up arrow" key is pressed. Operation buttons/keys perform binary operations between the accumulator and the topmost stack element. Finally copy of the result is pushed back onto the stack, so next number typed in may be used for the next computation.

The btxt list of characters defines what shows on buttons.

The button creation function (cbtn) defines a <DIV> element nesting a <BUTTON> element. Each button has an Activator based on evtBCastA that maps each click to the character showing on the button. Note the float: left style and percentage width defined for <DIV>s: no matrix layout logic is necessary; buttons fill the <DIV> with borders with correct placement.