[web-devel] type safe web forms at compile time Was: Re: [Haskell-cafe] Ur vs Haskell

Alberto G. Corona agocorona at gmail.com
Wed Mar 2 21:53:28 CET 2011


Hi.

Some time ago I forgot to forward this message to thie ur versus Haskell
<http://www.haskell.org/pipermail/haskell-cafe/2011-January/088060.html>discussion,
(as usual)
---
The most impressive feature (of ur) is the compile time checking of
conformance between the  form and  the form results. This can be done in
Haskell using HList magic and
some class instances, I guess.
----
Since then I have been playing mentally with this. Recently I found
 something
simple an interesting enough to share. (Although crude).

 It is a kind of typed form fields

data Input a=   Input String Type a (String -> Either String a)


and a kind of heterogeneous list  to aggregate form fields and results with
the operator (:*):
    Input a :*  Input b ;* Input c....
     a :* b :* c

and a (simulated for the purpose of demonstration)  send-receive function
 that type match the form fields and the results:


*Main> let form = Input "" Text "stringdata" novalidate :* Input "" Text
(1::Integer) novalidate

*Main> ask form  >>= \(a :* b) -> return $ a ++ b

<interactive>:1:0:
    No instance for (FormDigest
                       (Input [Char] :* Input Integer) ([a] :* [a]))
      ......

notifying that there is no translation defined , because the result requires
two lists of the same type when the form gives a string and an Integer

But forcing the correct monomorphic types it does pattern match and return
the values.


*Main> ask form  >>= \ (a :* b) -> print ('s':a) >> print ( fromInteger $ b)
"sstringdata"
1


ask is just a simulation of HTTP one time interaction. It returns the input
values.
The whole loop involves the rendering of the form, with render:

*Main> render form
<input type="Text" name="var1" value="stringdata"/>
<input type="Text" name="var2" value=1/>

In a real case the results are read and validated from the the  post
values.They
are  (or can be) ordered sequentially acording with Input field names.
The FormDigest instances do this work. There is no need to define new
FormDigest instances. (although non one to one field-result can be created)

The text is in literate haskell. There is a more elaborate example at the
end.
I know that the instances are non tail recursive and there are factorization
pending
 but this is just a proof of concept:

>  {-# LANGUAGE
>      FlexibleInstances,
>      MultiParamTypeClasses,
>      TypeOperators
>  #-}

> import Control.Monad.State

The Heterogeneous list agregator. I tried to use GADTs but they does not
easily pattern match

> data x :* xs =   x :* xs deriving (Read, Show, Eq)
> infixr 5 :*


> data Type= Hidden | Text deriving (Show, Read)    -- to add all the types

the input field, with text formatting, initial value and runtime validator

> data Input  a =   Input String Type  a (String -> Either [String] a)

> instance(Show a)=> Show (Input a) where
>   show (Input _ _ x _) = show x

rendering of the form need a sequentiation of field names. I use a state
monad for this

> class RenderForm a  where
>  renderForm ::  a -> State Int String

> instance  (Show a) => RenderForm  (Input a) where
>  renderForm  input = do
>     s1 <- render1 input
>     n <- get
>     put $ n + 1
>     return  s1

HList school here:

> instance (Show a,RenderForm xs) => RenderForm (Input a :* xs) where
>  renderForm  (input :* xs)= do
>    n <- get
>    put $ n+1
>    h <- render1 input
>    s <- renderForm  xs
>    return $ h++s

> render1 (Input msg t x _)= do
>    n <- get
>    put $ n+1
>    return $ msg
>            ++ "<input type=\""
>            ++ show t ++ "\" name="
>            ++ "\"var"++show n ++ "\" value="
>            ++ show x ++"/>\n"
>

> render form=    putStrLn $ evalState (renderForm   form ) 0

processing of the returned form result, in an ordered String list, according
with
seuquential names of the fields defined in renderForm.

> class  FormDigest a  b where
>  formDigest :: a ->  [String] -> Either [String]  b

"Input a" is diggested into a type "a"

> instance FormDigest (Input a) (a) where
>   formDigest (Input _ _ x f) (s: ss)= case f s of
>       Right x -> Right $ x
>       Left x  -> Left x

recursively add instances for any  list  of inputs
Input a's are diggested into a's

> instance  FormDigest as bs
>           => FormDigest (Input a :* as) (a :* bs) where
>  formDigest (input :* fs) es@(s:ss) =
>       let er = formDigest fs ss
>           e  = formDigest input es
>       in case (e, er) of
>           (Right x, Right  ys) ->  Right $ x :* ys
>           (Right _, Left errs) -> Left errs
>           (Left err, Left errs) ->  Left (err ++ errs)



simulated request-response that returns the entered input values

> sendRec xs= do
>   let strs =   showValues xs
>   return $ formDigest xs  strs

> class ShowValues a where
>    showValues :: a -> [String]

> instance Show x => ShowValues (Input x) where
>     showValues i = [show i ]

> instance (Show x,ShowValues xs) => ShowValues (Input x :* xs) where
>     showValues (i :* xs)= show i : showValues xs

end of simulated request response

> ask :: (ShowValues a,  FormDigest a b) => a -> IO b
> ask form = do
>   er <- sendRec form
>   case er of
>     Left errs  -> error "" --  shoud be: "ask1 errs  form "·to render form
and errors
>     Right res -> return res


EXAMPLE:

> data Emp= Emp{name::String, salary :: Int} deriving Show

> emp= Emp "Luis" 10000

toy html operators:

> b  msg  =   ("<b> " ++ msg ++ " </b>\n")
> p  msg  =   ("<p> " ++ msg ++ " </p>\n")

> novalidate n=  Right $ read n

> main= do

>
>   let form  =   Input
>                  (   b  "please enter the name"
>                  ++  p "mas texto")
>                    Text (name emp) novalidate
>                 :* Input
>                  (b  "please enter the salary"
>                  ++  p  "jkjkjk")
>                    Text (salary emp) novalidate

>   render form

the matching thing

>   (n :* s ) <- ask   form

>   print emp
>   print $ Emp n s
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110302/6707c9ea/attachment.htm>


More information about the web-devel mailing list