Document not found! Please try again

WASH/CGI: Server-side Web Scripting with Sessions ... - CiteSeerX

14 downloads 0 Views 186KB Size Report
Page 1. Page 2. Page 3. Page 4. Page 5. Page 6. Page 7. Page 8. Page 9. Page 10. Page 11. Page 12. Page 13.
WASH/CGI: Server-side Web Scripting with Sessions, Compositional Forms, and Graphics Peter Thiemann Universitat ¨ Freiburg Germany

ABSTRACT

program and starts it in a new pro ess. This kind of program is alled a CGI s ript. It re eives its input through the standard input stream and through environment variables and delivers the response to its standard output stream. The CGI standard [4℄ xes the format of this ommuni ation.

WASH/CGI is a domain spe i embedded language for server-side Web s ripting. It is implemented and hosted in Haskell. Its implementation relies on CGI, but it avoids most of CGI's drawba ks by in orporating the on ept of a session and by providing a ompositional approa h to onstru ting intera tion elements (forms). From a programmer's perspe tive, programming WASH/CGI is like programming a graphi al user interfa e (GUI). In ontrast to a GUI, the layout is spe i ed using HTML. WASH/CGI generates HTML via a new monadi interfa e. Spe ial ombinators are available that provide typed input elds and graphi s, whi h is generated on the y.

Unfortunately, there are a number of limitations. The most painful one stems from the fa t that the underlying HTTP proto ol, whi h is used for ommuni ation between browser and server, is stateless. Every single request starts a CGI s ript. Then the s ript produ es a response page and terminates. Hen e, there is no on ept of a session, i.e., a sequen e of alternating requests and responses. Usually, CGI programmers must build su h sessions from s rat h. They distribute the stages of a session over a number of CGI s ripts and onne t them manually through links in the response pages. To provide a notion of session-wise state they must resort to putting hidden information in their responses (hidden input elds) or to using ookies, whi h is not reliable be ause browsers an refuse them. Clearly, it is error-prone to manually maintain links in this way and also to have the ode for a single intera tion for ibly spread over many programs.

The ommon gateway interfa e (CGI) is one of the prevalent methods to provide dynami ontents on the Web. Sin e it is

umbersome to use in its raw form, there are many libraries that make CGI programming easier.

Keywords

Haskell, Monads, GUI Programming

1.

INTRODUCTION

The ommon gateway interfa e (CGI) is one of the oldest methods for deploying dynami Web pages based on server-side omputations. As su h, CGI has a number of advantages. Virtually every Web server supports CGI. CGI requires no spe ial fun tionality from the browser, apart from the standard support for form elements in HTML. On the programming side, CGI ommuni ates via standard input/output streams and environment variables. It is not tied to a parti ular ar hite ture or implementation language. Hen e, CGI is the most portable approa h to providing dynami ontents on the Web. The basi idea of CGI is straightforward. Whenever the Web server re eives a request for a CGI-enabled URL, it treats the lo al le determined by the URL as an exe utable

Another sour e of errors lies in the parameter passing s heme between forms and CGI s ripts. A form is an HTML element that ontains named input elements. Ea h input element implements one parti ular kind of input behavior (a widget in GUI terminology). When a spe ial submit button is pressed, the browser sends a list of pairs of input element names and their string values to the server. Inside of a CGI s ript, these argument values an be a

essed by their name. Unfortunately, there is no guarantee that the form uses the names expe ted by the s ript and vi e versa. Last but not least, all parameter passing between forms and CGI s ripts is ompletely untyped. Ea h s ript must provide its own de oding fun tions to onvert strings into whatever type is really required. It is not even possible to spe ify the expe ted type of an input eld. The present work provides a ure for all the issues mentioned above: the DSL WASH/CGI. WASH/CGI makes CGI programming easy and intuitive. It is implemented as a library for Haskell [9℄ and provides the following features:  one program an implement entire sessions;  the spe i ation of an input eld and the olle tion of

the input from this widget are tied together so that mismat hes are not possible; the external name of an input eld does not matter;  input elds are rst- lass entities; they may be typed

and grouped to ompound input elds ( ompositionality); ea h group may be bound to a allba k a tion;

 rst- lass images as a tive input elds where ea h pixel

of the image an result in a di erent a tion;

 no expli it URLs need to be onstru ted in the s ript,

ex ept referen es to external pages;

 the s ript is \relo atable"; it an be moved in the di-

re tory hierar hy or to another server without hange1 .

The library is available through the WASH web page [20℄. The web page also provides some live examples, omplete with sour es. Familiarity with the Haskell language [9℄ as well as with the essential HTML elements is assumed throughout.

2.

EXAMPLE PROGRAMS

This se tion demonstrates the use of WASH/CGI with some examples. At rst, the reader may be surprised that the examples have a distin t GUI avor. But this is exa tly the right impression: CGI programming should feel just like GUI programming, where the layout is determined by HTML. The library is based on the monad CGI, whi h handles all intera tion with the browser.

2.1 Hello world

mainCGI :: CGI () mainCGI = htell (standardPage "Hello World" empty)

As ustomary, the rst program just displays Hello World on the s reen. The ombinator htell takes an HTML page produ ed by standardPage and sends it to the browser. The

ombinator standardPage takes a title and the ontents of the HTML page (here: empty) and produ es the usual ombination of html, head, body, and title tags. standardPage ttl elems = html (head (title (text ttl)) ## body (h1 (text ttl) ## elems))

Here, text transforms a string into an HTML element and the operator ## on atenates groups of HTML elements. Hen e, the browser re eives the following response: Hello World

Hello World

1 Of ourse, provided that it an exe ute at all on the other ma hine.

mainCGI :: CGI () mainCGI =

ounter 0

ounter :: Int -> CGI ()

ounter n = ask (standardPage "Counter" $ makeForm $ do text "Current ounter value " text (show n) br empty submitField ( ounter (n + 1)) (fieldVALUE "In rement"))

Figure 1: The ounter example

2.2 The counter example

The ounter example (Fig. 1) uses the makeForm ombinator to start a form. The ontents of the form are spe i ed using a monad. Every ontent element (in fa t, every HTML element) is a value in the monad WithHTML CGI. The text

ombinator produ es plain text output, the br empty inserts a
element, and the submitField reates a submitbutton. The rst parameter of submitField is the a tion to be taken, when the form is submitted. The se ond parameter spe i es the attributes of the submit-button. The empty parameter of br an also be repla ed by attributes for
.

2.3 Extended counter

ounter :: Int -> CGI ()

ounter n = ask $ standardPage "UpDownCounter" $ makeForm $ do text "Current ounter value " a tiveInputField ounter (fieldVALUE (show n)) submitField ( ounter (n + 1)) (fieldVALUE "++") submitField ( ounter (n - 1)) (fieldVALUE "--")

In this example, we onsider a repla ement for the ounter fun tion from the previous example. It displays the urrent value in an input eld and it has two submit-buttons. The generated Web page has the following fun tionality: Cli king on the ++ and -- button in rements or de rements the

ounter's value. Alternatively, a new value may be entered by typing it into the a tiveInputField and hitting return to submit the form. The input eld is a tually typed. It a

epts only inputs that parse as elements of type Int: a tiveInputField :: Read a => (a -> CGI ()) -> HTMLField (InputField a)

2.4 Calculator

A po ket al ulator onsists of a display and an array of buttons (Fig. 2). The orresponding ode uses a HTML table to spe ify the layout (Fig. 3). Ea h button has an a tion, spe i ed by al A tion, atta hed to it. The textInputField is a spe ialized input eld for Strings. In luding it into a form yields a value dsp of type InputField String. This value is a handle to extra t the input from the eld using the fun tion value :: InputField a -> Maybe a.

The table, tr, and td fun tions onstru t HTML elements with the same tag. The argument of ea h fun tion spe i es the list of sub-elements and attributes of the element. The operator ## serves to on atenate (lists of) HTML elements and attributes. In the example ode, td (textInputField (fieldVALUE dstr) ## attr " olspan" "4")

reates the element

2.5 Graphics

mainCGI = ask $ standardPage "UseGraphi s" $ makeForm $ a tiveImage testImage

Figure 2: S reenshot of Cal ulator

anvasRed = newImage (100,100) red ovalBlue = fillOval anvasRed (20,20) (70,50) blue ba kground = a tivate ovalBlue hitNothing testImage = a tivateColor ba kground blue hitOval hitOval = htell (standardPage "Hit the Oval!" empty) hitNothing = htell (standardPage "Missed." empty)

mainCGI :: CGI () mainCGI =

al "0" id

red = (255,0,0) blue = (0,0,255)

al :: String -> (Integer -> Integer) -> CGI ()

al dstr f = ask $ standardPage "Cal ulator" $ makeForm $ table $ do dsp Char -> (Integer -> Integer) -> CGI ()

al A tion dsp f | isDigit = al (dstr ++ [ ℄) f | == 'C' = mainCGI | == '=' =

al (show (f (read dstr :: Integer))) id | otherwise =

al "0" (optable (read dstr :: Integer)) where Just dstr = value dsp optable '+' = (+) optable '-' = (-) optable '*' = (*) optable '/' = div

Figure 3: Cal ulator

3. USER-LEVEL CONCEPTS

This se tion presents an appli ation programmer's view of the on epts and fun tion of WASH/CGI.

3.1 HTML

Ea h HTML element is onstru ted by a fun tion of the same name as shown with the fun tion table below. Ea h of these \ onstru tor fun tions" has a type like type HTMLCons m a = WithHTML m a -> WithHTML m a table :: Monad m => HTMLCons m a

There are also onstru tor fun tions for attributes that will be atta hed to the en losing element. The generi attribute

onstru tor is attr. attr :: Monad m => String -> String -> WithHTML m ()

It onstru ts an attribute instan e from an attribute name and an attribute value. Although a value of type WithHTML m a stands for an ordered olle tion of HTML elements and attributes, it is impossible to examine elements and attributes on e they are

onstru ted. Passing su h a value to a onstru tor fun tion in orporates the elements as sub-elements of the new element and also atta hes the attributes to it. The values empty :: Monad m => WithHTML m () (##) :: Monad m => WithHTML m a -> WithHTML m b -> WithHTML m a

serve as the empty olle tion and as the on atenation operation. Sin e WithHTML m is a monad (provided that m is), HTML elements may also be ombined using the standard monad operations as well as the do notation. In most ases, the parameter m will be the monad CGI. But there are ex eptions, as we will see below in 3.4.

3.2 Input fields

There are spe ial ombinators to onstru t input elds. They add an input eld to the urrent olle tion of HTML elements and return a handle for a

essing the input value. The type of su h an input eld is type HTMLField a = WithHTML CGI () -> WithHTML CGI a

That is, it takes a olle tion of attributes (of type WithHTML CGI ()), atta hes them to a new eld, and embeds the new eld into another olle tion. The generi , typed textual input eld is onstru ted by inputField :: Read a => HTMLField (InputField a)

The Read a predi ate omes from the fa t that all ommuni ation between browser and server is through strings. Hen e, ea h value of type a must be onverted from a string. On e again, the value of type InputField a is merely a handle to a

ess its input values through the two fun tions value :: InputField a -> Maybe a string :: InputField a -> Maybe String

The value fun tion provides a

ess to the parsed value (if there was a parsable input), whereas the string fun tion is meant for error analysis and provides a

ess to the raw input (if the input element was lled in at all). The remaining input elements are provided in the same manner (see Fig. 4). A fileInputField returns the ontents of the hosen le as a string. A resetField just lears all input elds, it has no I/O fun tionality. Radio buttons and

passwordInputField

he kboxInputField fileInputField resetField submitField

:: :: :: :: ::

HTMLField HTMLField HTMLField HTMLField CGI () ->

(InputField String) (InputField Bool) (InputField String) (InputField ()) HTMLField ()

Figure 4: Input elds (ex erpt) sele tion boxes have a slightly more ompli ated interfa e. They are omitted for brevity. It remains to dis uss the submitField. It takes a CGI a tion and generates a button in the HTML page. Cli king su h a button exe utes its a tion. The a tion is similar to a ontinuation. Sin e a form may ontain more than one submit button, multiple ontinuations are possible. In parti ular, a large form may be omposed from small intera tion groups that onsist of input elds and one or more submit buttons.

3.3 Forms

makeForm :: HTMLField ()

The onstru tor for forms takes a olle tion of attributes and returns a element. At least one form is ne essary in ea h page that ontains input elds sin e input elds do not make sense outside of a form. It is not ne essary to set the standard attributes of the form element. The a tion attribute, whi h ontains the URL for pro essing the form's

ontents, the en type attribute, whi h determines the en oding of the form's ontents, and the method attribute are all determined automati ally by WASH/CGI.

3.4 Sessions

Programming of intera tions is based on just four ombinators in the monad CGI. run ask tell io

:: :: :: ::

Translation -> CGI () -> IO () WithHTML CGI a -> CGI () CGIOutput a => a -> CGI () (Read a, Show a) => IO a -> CGI a

The ombinator run introdu es the CGI monad. The standard main program (for the examples above) is as follows: main = run NoTranslation mainCGI

The NoTranslation argument is appropriate for all s ripts that do not make use of graphi s generation (see Se . 3.5). The ombinator ask displays a page on the browser. Its argument of type WithHTML CGI a onstru ts a web page, whi h should ontain a form. It returns a CGI a tion. This a tion never produ es its value. To extra t values from the form, a allba k a tion must be tied to one of its input elements. The ombinator tell displays a page and terminates the intera tion. The argument of tell an have any type of

-- inserting into HTML a tiveImage :: CGIImage -> WithHTML CGI () -- reating new images newImage :: (Int, Int) -> Pixel -> CGIImage makeText :: String -> Pixel -> CGIImage gifImage :: String -> CGIImage -- drawing drawOval, fillOval, drawRe tangle, fillRe tangle, drawLine :: CGIImage -> (Int, Int) -> (Int, Int) -> Pixel -> CGIImage -- omposing images overlay :: CGIImage -> CGIImage -> (Int, Int) -> Pixel -> CGIImage -- atta hing a tions type A tionFun = Int -> Int -> Maybe (CGI ()) a tivateXY :: CGIImage -> A tionFun -> CGIImage a tivate :: CGIImage -> CGI () -> CGIImage a tivateColor :: CGIImage -> Pixel -> CGI () -> CGIImage

ask

ask

io

ask

tell

Figure 6: A CGI session inparm

=

resp1 ask

:

[] ask

Figure 5: Interfa e for graphi s

Figure 7: Partial CGI session

lass CGIOutput. These types are Status (error message), Lo ation (redire t response to a URL), and WithHTML IO a (a HTML page). A tually, tell is a member fun tion of CGIOutput. Appendix A ontains some instan e de nitions.

The CGIInfo argument ontains the omputed URL of the s ript, the ontent type of the input to the s ript, and the raw input stream.

The ombinator io inje ts an IO a tion into the CGI monad.

On submission of a form, the browser sends an en oded version of a list of pairs of the form eldname = value to the Web server. In this list, eldname is the name of an input eld and value is the value entered by the user. The argument list of type [CGIParameter℄ is the de oded version of this list. It an be a

essed like a nite map using the following lookup fun tions for parameter lists:

3.5 Graphics

asso Parm

lass CGIOutput a where tell :: a -> CGI ()

giPut :: a -> IO ()

Many web pages ontain graphi s that are prefabri ated. The WASH/CGI library ontains fa ilities to reate simple, li k-sensitive graphi s on the y. As expe ted from a fun tional language, an image is a rst- lass value. Images

an be reated from s rat h (newImage), from text strings (makeText), and from existing GIF images (gifImage). They

an be manipulated in the usual ways by drawing ovals, re tangles, and lines and by overlaying one image on top of another (see Figure 5 for a summary of the interfa e). In addition, CGI a tions may be atta hed to parts of an image using a tivate, a tivateXY, and a tivateColor. Finally, an image an be inserted into a web page using a tiveImage. In prin iple, it is possible to write intera tive graphi s programs, although the intera tion is a bit slow.

4. IMPLEMENTATION 4.1 Raw CGI functionality

The module RawCGI implements the input part of the low level CGI fun tionality. It is usually invisible to a WASH/CGI programmer. Its interfa e is the fun tion start: start :: (CGIInfo -> [CGIParameter℄ -> IO a) -> IO a

It reads and de odes the information passed to the CGI s ript in environment variables and through the standard input. This information is passed to the rst argument, whi h is supposed to generate the output of the CGI s ript.

:: String -> [CGIParameter℄ -> Maybe String

4.2 Session management

Figure 6 shows a CGI session as it looks to the WASH/CGI programmer and also to the user. A session is a dynami ally evolving sequen e of ask and io a tions (in the CGI monad). Ea h of these a tions queries the external world, either by displaying a form on a Web browser or by performing and IO a tion, and re eives a response. At ea h point of the session, the previous responses determine the next CGI a tion. Unfortunately, whenever a response is required from the Web browser, we know that the CGI s ript must terminate. Thus, when the response omes ba k, we need a way to get ba k to the a tion that is waiting for it. To do so, it is ne essary to keep tra k of all the responses that have been re eived up to that a tion. These responses are put into a hidden input eld on the form, so that they an be re onstru ted on the next invo ation of the CGI s ript. Hidden elds are not displayed but they are always sent along when the form is submitted. Thus the hidden eld plays the role of a ontinuation. For illustration, Figure 7 shows a pre x of the CGI session after the rst ask has been ompleted and the se ond ask has delivered its form to the browser. The list inparm is the list of responses to previous a tions. Its resp1 orresponds to the response to the rst ask. If an ask (or io) has a orresponding value in the inparm list, then this value is taken as the response, without sending anything to the browser.

At the se ond ask, the list inparm is empty, hen e the CGI monad must generate the form and get the response from the browser. On the next invo ation of the CGI s ript, the value of inparm is resp1 : resp2 : [℄ so that both ask a tions take their responses from the list. Then the next a tion takes over and

omputes its response.

4.2.1 The types

data CGI a = CGI { unCGI :: CGIState -> IO (a, CGIState) } data CGIState = CGIState { inparm :: [PARAMETER℄ , outparm :: [PARAMETER℄ , giInfo :: CGIInfo , pageInfo :: PageInfo } data PARAMETER = PAR_RESULT String | PAR_VALUES [CGIParameter℄ deriving (Show, Read)

The CGI monad is a state monad omposed with the IO monad. The state of type CGIState ontains two lists with elements of type PARAMETER, the giInfo re ord passed by RawCGI.start, and some data about the urrently generated page in pageInfo. While giInfo remains onstant, pageInfo evolves ontinually as requests and responses are pro essed.

tains the parameters for the urrent form if they an be

omputed from the inparm eld. The en type eld ontains the ontent type of the most re ently submitted form (in this session). Finally, the nexta tion eld determines the CGI a tion to be exe uted after the output page has been

omputed. This a tion is either simply to display the page or it is the a tion spe i ed in a submit eld.

4.2.2 The actions Now that we have gathered the basi intuitions and the basi types involved, we an look at the ode of io: io :: (Read a, Show a) => IO a -> CGI a io ioA tion = CGI (\ gistate ->

ase inparm gistate of -- parameter of orre t form present: -extra t result PAR_RESULT aStr : rest -> return (read aStr, nextCGIState gistate) -- no parameter present: -perform a tion and prepend result [℄ -> do a reportError "Out of syn " empty gistate)

The datatype PARAMETER is the type of responses from CGI The fun tion nextCGIState has two duties. It drops the rst a tions. The result of an io a tion orresponds to a PAR_RESULT str element of the inparm eld, whi h belongs to the urrent and an ask a tion orresponds to a PAR_VALUES str rea tion, and it re-initializes the pageInfo eld.2 sponse. In ea h ase the results are en oded in a string using methods of Read and Show. The list inparm ontains the responses to previous a tions in the order that they o

urred. It indi ates the path from the start of the intera tion to the urrent a tion. Ea h ask or io a tion takes its response from the rst element of inparm and passes its tail to the remaining a tions. The list outparm initially ontains the same values as inparm, but in reverse order. This eld plays the role of the history log. Whenever a new response is omputed, it is put in front of this list. This outparm list is a tually put in the hidden input eld of every form. The pageInfo eld ontains all information to generate input elements and forms and for extra ting results from them. It is reset by every ask and io a tion. data PageInfo = PageInfo { ount , bindings , en type , nexta tion }

:: :: :: ::

Int Maybe CGIParameters String Element -> CGI ()

The CGI monad generates unique names for input elements and forms from the ount eld. The eld bindings on-

nextCGIState gistate = gistate' where gistate' = gistate { inparm = drop 1 (inparm gistate) , pageInfo = initialPageInfo gistate' }

The initialPageInfo sets the ount to 0 and it extra ts the

urrent bindings from the rst element of the inparm eld of the CGI state. The en type is also initialized from the state. The nexta tion eld is either tell (if there are no parameters for this form, then the form must be displayed on the browser) or it is tellError (whi h generates an error unless an input eld overrides the a tion). initialPageInfo gistate = let bnds = do PAR_VALUES parms [Attribute℄ -> [Element℄ -> Element :: [String℄ -> [Element℄ -> Element

attr_

:: String -> String -> Attribute

add_ :: Element -> Element -> Element add_attr_ :: Element -> Attribute -> Element

Figure 8: Signature of

}

HTMLBase

(ex erpt)

Nothing -> tell Just _ -> tellError "Unspe ified a tion"

This leaves not mu h to do for the ombinator ask. It rst builds the output do ument from its argument of type WithHTML CGI a using build_do ument, whi h may hange the nexta tion eld, then it extra ts the nexta tion eld from the pageInfo and applies it to the do ument just onstru ted. The resulting CGI a tion is applied to the next CGI state. To reiterate, if there are no parameters for this do ument (or rather for its form), then it displays the do ument. Otherwise, some a tion is performed that is olle ted while onstru ting the do ument. ask :: WithHTML CGI a -> CGI () ask ma = do elem unCGI (nexta tion (pageInfo gistate) elem) (nextCGIState gistate)

We defer the dis ussion of run's implementation to Se tion 4.7 be ause it is easier to look inside the monad WithHTML CGI rst, to see how input elds really work. But before we

an do that, we have to onsider the generation of HTML.

4.3 Generating HTML

The low-level module HTMLBase provides some simple fun tionality for generting raw HTML (Fig. 8). The onstru tors element_ and do type_ onstru t ordinary elements and the top-level element of a do ument, attr_ onstru ts an attribute from the name and the value string, add_ e e' appends e' to the list of sub-elements of e, and add_attr_ atta hes an attribute to an element. The monad transformer WithHTML adds to any monad m a

omponent that generates HTML. To this end, it omposes m with a state monad that propagates a urrently onstru ted HTML element. The return, >>=, and lift operations are standard, and thus omitted.

table :: Monad m => WithHTML m a -> WithHTML m a table ma = WithHTML (\elem -> unWithHTML ma (element_ "table" [℄ [℄) >>= \(a, tableElem) -> return (a, add_ elem tableElem))

Here, element_ onstru ts a element with empty attribute list and empty sub-element list. This element is rst transformed by unWithHTML ma, whi h atta hes attributes and adds sub-elements to it. Finally, the omplete
element is added to the urrent element elem. Attributes are also atta hed to the urrent element. The

orresponding fun tion attr is straightforward. attr :: Monad m => String -> String -> WithHTML m () attr a v = WithHTML (\ elem -> return ((), add_attr_ elem (attr_ a v)))

The top-level fun tion build_do ument onstru ts the outermost de laration using the low-level fun tion do type_, passes it to the monad that lls it with ontent, and returns the full element in the end. build_do ument :: Monad m => WithHTML m a -> m Element build_do ument ma = unWithHTML ma (do type_ ["HTML" ,"PUBLIC" ,"\"-//W3C//DTD HTML 4.01//EN\"" ,"\"http://www.w3.org/TR/html4/stri t.dtd\""℄ [℄) >>= \ (a, elem) -> return elem

The implementations of empty and the gluing operator ## are unsurprising. empty orresponds to return and gluing is the monad's bind operator, modi ed to return the result of the rst a tion. empty :: Monad m => WithHTML m () empty = return () (##)

:: Monad m => WithHTML m a -> WithHTML m b -> WithHTML m a x ## y = x >>= \a -> y >> return a

The remaining fun tions are routine. More interesting are the fun tions that onstru t input elds. They live in the monad WithHTML CGI, whi h is dis ussed next.

4.4 The monad WithHTML

CGI

data WithHTML m a = WithHTML { unWithHTML :: Element -> m (a, Element) }

A typed input eld takes a olle tion of attributes, atta hes them to an element, and yields the input eld.

Ea h element-produ ing ombinator adds to the urrent element, as demonstrated with the table ombinator.

type HTMLField a = WithHTML CGI () -> WithHTML CGI a inputField :: Read a => HTMLField (InputField a)

The ombinator has three obligations.

do ontents name CGI (URL, A tionFun) flushImage img = The value NoTranslation indi ates that this feature of WASH/CGI do giImage CGI () -> IO () run translator (CGI gi) = start $ \ info de oded -> do let maybeparm = liftM (read . urlDe ode) $ asso Parm "=CGI=parm=" de oded oldparm = ase maybeparm of Just parm -> parm Nothing -> [℄ newparm | null de oded = [℄ | otherwise = (PAR_VALUES $ dropHidden de oded) : oldparm

gistate = CGIState { inparm = reverse newparm , outparm = newparm , giInfo = info , pageInfo = initialPageInfo gistate }

Re all that the outparm eld ontains the log of the results of io a tions and the inputs to ask a tions in reverse order. The rst part of the ode reads the old outparm value and forms its value for the urrent exe ution by prepending the newly a quired input parameters for the urrent form. As already explained before, the value of inparm is the reverse of outparm. The giInfo and pageInfo elds are simply set to their initial values. The next part deals with the Translation argument and starts the monad. args

gi gistate >> return () Translation trans -> if null args then gi gistate >> return ()

else giPut (trans args) exitWith ExitSu

ess

A CGI s ript an re ognize the presen e of a query string by looking for its argument list (using System.getArgs). If there is neither a translation nor a query string, then the

ode runs the gi a tion on the initial state gistate. Otherwise, it outputs the result of translating the query string using the giPut method of the lass CGIOutput.

5. DISCUSSION

In nished produ ts, it is sometimes un lear how and why design de isions were made. The present design evolved through a number of steps. The rst two subse tions dis uss two obsolete approa hes and explain their short omings.

5.1 No monads

In the rst design, the type Element of HTML elements was freely a

essible. Furthermore, Element had to be parameterized over the type of return values of a form. In this approa h, the type of a few representative ombinators was as follows. ask :: String -> [Element (Colle t m)℄ -> CGI m makeForm :: m -> [Element (Colle t m)℄ -> Element (Colle t m) makeInputField :: (Read a) => FieldConfig a -> (m -> a -> m) -> Element (Colle t m)

The CGI a tion ask title elems displays a HTML page with title title where elems may ontain as many forms as desired. The a tion returns the a tual typed values for the input elds of the submitted form. The type Colle t m is de ned as follows: data Colle t m = I m | T (String -> m -> Maybe m)

The idea is that the type m is a state that is threaded through the whole form. Ea h input eld updates it. In the end, it be omes the form's return value. The value I m spe i es the value of the initial state. The value T f spe i es a parsing fun tion that maps the input string and the urrent state to the next state (if the input string was parsable). Hen e, the makeForm q elems a tion is parameterized over an initial value q for the state and the list of elements that make up the ontents of the form. Finally, makeInputField

onf upd takes a list of on guration options for the eld and an update fun tion that integrates the value of the eld into the state. Typi ally, the type m is a re ord type and the update fun tions are re ord- eld updates. This approa h has a number of drawba ks. First, it is not possible to re-use an existing HTML library be ause none provided the ne essary parameterization. Se ond, be ause of the parameterization forms and form elements annot be

freely ombined into a web page. All elements in a page must share a single type. This is quite restri tive and dis ourages re-use of form omponents. Third, programming and use of the update fun tions is error-prone, so that di erent input elds may a

identally update the same omponent. Fourth, it is not possible to use a allba k-style of programming.

5.2 Imperative approach

In some GUI toolkits, in parti ular TkGofer [5℄ and its des endant T lHaskell, the reation of a widget returns a handle to the widget, whi h is later on used to a

ess the widget. In our orresponding approa h to the CGI library, there were a tions in the CGI monad to reate input elds. The HTML

ode was reated separately from the resulting handles. Putting the widget reation dire tly into the CGI monad is unsafe be ause the handle of one eld may be used multiple times to generate its HTML representation. Even worse, it is possible to pass su h a handle into a di erent form. Clearly, this plays havo to our parameter-passing me hanism, whi h relies on the uniqueness and the lo ality of the names assigned to input elements. These issues ould have been addressed using an advan ed type system, but the requirements (linearity ould enfor e that ea h handle is used exa tly on e) go well beyond Haskell's apabilities.

5.3 Screen layout

It might be argued that the monadi organization of the HTML generation for es parti ular s reen layouts, whi h is

ertainly a bad thing from the GUI designer's point of view. For example, it is easy to reate input elds and refer to them \from the right" or \from below": do f1 CGI ()

giPut :: a -> IO () -tell a = CGI (\ gistate -> giPut a >> exitWith ExitSu

ess) instan e CGIOutput (WithHTML IO a) where

giPut hma = do elem >= putStr -- a redire tion data Lo ation = Lo ation URL instan e CGIOutput Lo ation where

giPut (Lo ation url) = do putStr "Lo ation: " putStrLn url putStrLn ""