{-# OPTIONS -F -pgmFtrhsx -XUndecidableInstances -XOverlappingInstances -XTypeSynonymInstances -XFlexibleInstances #-} {- | Instantiation of "MFlow.Forms" for the hsp package it includes additional features for embedding widgets within HTML formatting -} module MFlow.Forms.HSP where import MFlow.Forms import Control.Monad.Trans import Data.Typeable import HSP import Data.Monoid import Control.Monad(when) import Data.ByteString.Lazy.Char8(unpack) instance Monoid (HSP XML) where mempty = mappend x y= <% x %> <% y %> mconcat xs= <% [<% x %> | x <- xs] %> instance FormInput (HSP XML) where fromString s = <% s %> finput typ name value checked onclick= s ; _ -> "")/> ftextarea name text= fselect name list= foption n v msel= where selected msel = if msel then "true" else "false" flink v str = <% str %> inred x= <% x %> formAction action form =
<% form %>
addAttributes tag attrs= tag <<@ map (\(n,v)-> n:=v) attrs