[Haskell-cafe] YAWQ (Yet Another Wash Question)

Matthias Neubauer neubauer at informatik.uni-freiburg.de
Fri Feb 25 10:15:55 EST 2005


John Goerzen <jgoerzen at complete.org> writes:

> Possible, but ugly.  I have about 50 lines of code that has to go
> in-between, so I'd be duplicating it.  And, if I tried to make it into
> just another function, I'd have the same problem, I believe (scoping)

It's all much easier: as always, you just have to use template
functions for all your pages. That's all you need ... :-)

Here is a recipe how I typically structure my WASH applications:

- First, I write down (html) code for all the web pages and abstract
  over all the varying parts (input fields, submit buttons,
  continuation pages, etc.). As result, I get (independent) template
  function for all the pages. Usually, each template function lives in
  a separate module/file.

- In the end, I write a *controller* function that both generates all
  the different pages by filling the holes of the templates and also
  ties together all the consecutive pages.

And that's all you need to solve your problem as well -- just use a
template function twice! Below, you'll find a small web app that
toggles between two varying input pages using the scheme I described
above.

-Matthias



module Main where

import CGI

main = run controller 

-- controller

controller :: CGI ()
controller = 
  let input1  = tr $ td $ textInputField empty
      submit1 = \ h cont -> submit h cont empty
      page1   = stepOneTemplate input1 submit1 page2

      out2    = \ t -> text t
      submit2 = \ cont -> submit0 cont empty
      page2   = stepTwoTemplate value out2 submit2 page3
     
      input3  = empty
      submit3 = \ h cont -> submit F0 cont empty
      page3   = stepOneTemplate input3 submit3 page4

      out4    = \ t -> text "No input, sorry!"
      submit4 = \ cont -> submit0 cont empty
      page4   = stepTwoTemplate (const undefined) out4 submit4 page1
  in page1

-- page templates

stepOneTemplate inputCode submitCode nextPage = do
  standardQuery "Input Page" $ table $ do
    do tr $ td $ text "Hello!"
       h <- inputCode 
       tr $ td $ text "Press the button!"
       tr $ td $ submitCode h nextPage

stepTwoTemplate validationCode outputCode submitCode nextPage h = do
  let i = validationCode h
  standardQuery "Result Page" $ table $ do
    tr $ td $ text "Your input was ..."
    tr $ td $ outputCode i
    tr $ td $ submitCode nextPage



-- 
Matthias Neubauer                                       |
Universität Freiburg, Institut für Informatik           | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052


More information about the Haskell-Cafe mailing list