Re: [Haskell-cafe] Problem with monadic formlets

2009-08-30 Thread Chris Eidhof

Hey everybody,

I've just uploaded formlets 0.6.1 to Hackage, which should fix this  
bug. Thanks for letting me know!


-chris

On 29 aug 2009, at 13:22, Jeremy Shaw wrote:


Hello,

Yeah, it seems that checkM in formlets 0.6 broken. I reported the  
bug to MightByte as well.


- jeremy

At Fri, 28 Aug 2009 12:49:08 +0100,
Colin Paul Adams wrote:



Colin == Colin Paul Adams co...@colina.demon.co.uk writes:



Jeremy == Jeremy Shaw jer...@n-heptane.com writes:


   Colin apparent data corruprion is occurring. I am suspecting a
   Colin bug in the formlets library (I have version 0.6).

   Colin So I have created a slightly cut-down (no database
   Colin involved) complete working program. Can you see if this
   Colin works ok with your version of formlets:

I managed to uninstall formlets-0.6 myself, and then installed 0.5
instead. After adding the necessary extra argument to runFormletState
(an empty string), the test program works fine. So this seems to be a
bug in formlets-0.6.
--
Colin Adams
Preston Lancashire

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-30 Thread Colin Paul Adams

Chris Hey everybody, I've just uploaded formlets 0.6.1 to
Chris Hackage, which should fix this bug. Thanks for letting me
Chris know!

Yes, it does fix it.

Thanks.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-29 Thread Jeremy Shaw
Hello,

Yeah, it seems that checkM in formlets 0.6 broken. I reported the bug to 
MightByte as well.

- jeremy

At Fri, 28 Aug 2009 12:49:08 +0100,
Colin Paul Adams wrote:
 
  Colin == Colin Paul Adams co...@colina.demon.co.uk writes:
 
  Jeremy == Jeremy Shaw jer...@n-heptane.com writes:
 
 Colin apparent data corruprion is occurring. I am suspecting a
 Colin bug in the formlets library (I have version 0.6).
 
 Colin So I have created a slightly cut-down (no database
 Colin involved) complete working program. Can you see if this
 Colin works ok with your version of formlets:
 
 I managed to uninstall formlets-0.6 myself, and then installed 0.5
 instead. After adding the necessary extra argument to runFormletState
 (an empty string), the test program works fine. So this seems to be a
 bug in formlets-0.6.
 -- 
 Colin Adams
 Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-29 Thread Jeremy Shaw
At Sat, 29 Aug 2009 15:46:42 +0100,
Chris Eidhof (formlets) wrote:
 
 Confirmed. checkM is broken, thanks for noticing! I'll have a look  
 into it, I'm not sure whether it can be fixed. I was thinking of  
 removing all the monadic stuff from the formlets. I think this will  
 make for a much cleaner interface, monadic checking can then be done  
 afterwards.

I am still a fan of (and use) this version of Form:

newtype Form xml m a = Form { deform :: Env - State FormState (Collector (m 
(Failing a)), xml, FormContentType) }

not sure how I would feel about the removal of 'm' from the
Collector. But 'xml' is nicer for me than 'm xml' because my collector
and xml generator are often in different monads. I can, of course make
them be in the same monad if I want:

type MyForm a = Form (IO XML) IO a

but I also have the option of just doing:

type MyForm a = Form (IO XML) IO a

or:

type MyForm a = Form (HSP XML) IO a

At present, I actually have my collector do all the validation and
update the database. As a use case, let's assume that the form is
creating a new user account. One possible error would be using a
username that is already in use. Doing that check requires a database
query. In fact, it seems best if it does a database update, so that
there is no race condition between checking if the name is in use, and
actually attempting to create the account with that username.

If you remove the ability to do IO in the collector, then I believe I
would need to:

 1. run the collector to do the pure part of the validation.

 2. if the pure part succeeds, use the returned value to do the impure
 validation

 3. if that fails, then redisplay the form using the same environment
 that I used for #1, but passing in the impure validation errors.

One potential drawback that I see with this is that it may make it
difficult to the pass the error messages back to the specific formlet
element that failed so that you can display the errors in-line.

[Note: the following discussion reflects the pre-0.6 design].

Currently the environment we pass in is something like:

type Env = [(String, Either String File)]

The first component of the tuple is the name of the element. aka,
input0, input1, etc.

I would propose that we also pass in a Failures argument:

type Failures = [(String, ErrorMsg)]

where the first component of the tuple is the name of the element
(input0, intpu1, etc) and the second element contains ErrorMsg.

or perhaps modify Env to:

type Env = [(String, (Maybe ErrorMsg, Either String File)]

We would need to modify the Failing data type to:

data Failing a = Failure [(String, ErrorMsg)] | Success a

so that Failures would contain their location. 

Not all errors correspond to a specific form element. Let's say that
you have 3 drop-down boxes that combine together to form a date
selector. You want to validate the result of all three combined to
make sure they picked a valid date, and if it is invalid, you produce
an error message for that group, not a specific element. The problem
then is that there is no 'location' that corresponds to that group, so
what do you put in the Failure tuple?

I think you can use freshName to generate an extra 'virtual' name that
corresponds to the group as a whole.

I have been meaning to prototype this in the near future and see if it
actually works. I'll try to get something worked up in the next two
weeks (my sister is getting married next week, so my schedule is
pretty full).

- jeremy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-28 Thread Colin Paul Adams
 Jeremy == Jeremy Shaw jer...@n-heptane.com writes:

Jeremy Hello, I hacked your code into a runnable example, and it
Jeremy seems to work for me.

Jeremy Which looks correct to me. Your code looks fine to me as
Jeremy well... Perhaps the error is not in the code you pasted,
Jeremy but somewhere else. I am running on an older, and somewhat
Jeremy forked version of Formlets, so there could also be a bug
Jeremy in the new code I guess. Though, that seems unlikely. But
Jeremy it is worth noting that we are not using the same version
Jeremy of the formlets library.

I did some debugging in ghci, but was unable to step through the
ensure and check routines, which is where the apparent data corruprion
is occurring. I am suspecting a bug in the formlets library (I have
version 0.6).

So I have created a slightly cut-down (no database involved) complete
working program. Can you see if this works ok with your version of
formlets:

module Main where

import Control.Applicative
import Control.Applicative.Error
import Control.Applicative.State
import Data.List as List
import Text.Formlets
import qualified Text.XHtml.Strict.Formlets as F
import qualified Text.XHtml.Strict as X
import Text.XHtml.Strict ((+++), ())
import Happstack.Server

type XForm a = F.XHtmlForm IO a

data Registration = Registration { regUser :: String
 , regPass :: String }
 deriving Show

handleRegistration :: ServerPartT IO Response
handleRegistration = withForm register register showErrorsInline (\u - 
okHtml $ regUser u ++  is successfully registered)

withForm :: String - XForm a - (X.Html - [String] - ServerPartT IO 
Response) - (a - ServerPartT IO Response) - ServerPartT IO Response 
withForm name frm handleErrors handleOk = dir name $ msum
  [ methodSP GET $ createForm [] frm = okHtml
  , withDataFn lookPairs $ \d -
  methodSP POST $ handleOk' $ simple d
  ]
  where
handleOk' d = do
  let (extractor, html, _) = runFormState d frm
  v - liftIO extractor  
  case v of
Failure faults - do 
  f - createForm d frm
  handleErrors f faults
Success s  - handleOk s
simple d = List.map (\(k,v) - (k, Left v)) d
 
showErrorsInline :: X.Html - [String] - ServerPartT IO Response
showErrorsInline renderedForm errors =
  okHtml $ X.toHtml (show errors) +++ renderedForm
 
createForm :: Env - XForm a - ServerPartT IO X.Html
createForm env frm = do
  let (extractor, xml, endState) = runFormState env frm
  xml' - liftIO xml
  return $ X.form X.! [X.method POST]  (xml' +++ X.submit submit Submit)
 
okHtml :: (X.HTML a) = a - ServerPartT IO Response
okHtml content = ok $ toResponse $ htmlPage $ content
 
htmlPage :: (X.HTML a) = a - X.Html
htmlPage content = (X.header  (X.thetitle  Testing forms))
  +++ (X.body  content)

register :: XForm Registration
register = Registration $ user * passConfirmed

user :: XForm String
user = pure_user `F.checkM` F.ensureM valid error where
valid name = return True
error = Username already exists in the database!
 
pure_user :: XForm String
pure_user = input `F.check` F.ensure valid error where
input = Username `label` F.input Nothing
valid = (= 3) . length
error = Username must be three characters or longer.

passConfirmed :: XForm String
passConfirmed = fst $ passwords `F.check` F.ensure equal error where
passwords = (,) $ pass Password * pass Password (confirm)
equal (a, b) = a == b
error = The entered passwords do not match!

pass :: String - XForm String
pass caption = input `F.check` F.ensure valid error where
input = caption `label` F.password Nothing
valid = (=6) . length
error = Password must be six characters or longer.

label :: String - XForm String - XForm String
label l = F.plug (\xhtml - X.p  (X.label  (l ++ : ) +++ xhtml))

main = simpleHTTP (nullConf {port = 9959}) handleRegistration

-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-28 Thread Colin Paul Adams
 Colin == Colin Paul Adams co...@colina.demon.co.uk writes:

 Jeremy == Jeremy Shaw jer...@n-heptane.com writes:

Colin apparent data corruprion is occurring. I am suspecting a
Colin bug in the formlets library (I have version 0.6).

Colin So I have created a slightly cut-down (no database
Colin involved) complete working program. Can you see if this
Colin works ok with your version of formlets:

I managed to uninstall formlets-0.6 myself, and then installed 0.5
instead. After adding the necessary extra argument to runFormletState
(an empty string), the test program works fine. So this seems to be a
bug in formlets-0.6.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem with monadic formlets

2009-08-27 Thread Colin Paul Adams
I'm trying to validate user input against a database (using HaskellDB,
but that doesn't seem to be the problem, as replacing the database
monadic code with return True gives the same problem.

This is part of my code:

register :: Database - XForm Registration
--register db = Registration $ pure_user * passConfirmed
register db = Registration $ (user db) * passConfirmed

user :: Database - XForm String
user db = pure_user `F.checkM` F.ensureM valid error where
valid name = do
  let q = do
t - table user_table
restrict (t!user_name .==. constant name)
return t
  rs - query db q
  return $ null rs
error = Username already exists in the database!
 
pure_user :: XForm String
pure_user = input `F.check` F.ensure valid error where
input = Username `label` F.input Nothing
valid = (= 3) . length
error = Username must be three characters or longer.

passConfirmed :: XForm String
passConfirmed = fst $ passwords `F.check` F.ensure equal error where
passwords = (,) $ pass Password * pass Password (confirm)
equal (a, b) = a == b
error = The entered passwords do not match!

pass :: String - XForm String
pass caption = input `F.check` F.ensure valid error where
input = caption `label` F.password Nothing
valid = (=6) . length
error = Password must be six characters or longer.

If I uncomment the commented line, and comment out the line after it
(in register), then everything works as expected. However, using it as
it is, one of the calls to pass gets the user's name for validation
(and consequently either fails if the user name is only 5 characters,
or the comparison of the two passwords fail (unless I type the user
name as the password).

I thought the applicative style meant the effects did not influence
one another, but here there is clear contamination. What am i doing wrong?
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monadic formlets

2009-08-27 Thread Jeremy Shaw
Hello,

I hacked your code into a runnable example, and it seems to work for me. What 
happens if you do something like:

 let (c, xml, _) = runFormState [(input0,Left name), (input1, Left 
password), (input2, Left password) ]  (register foo) in c = \r - 
do print xml  print r
(except you need to pass in a Database instead of foo as the argument to 
register.)

I get:

label
Username/label
input type=text name=input0 id=input0 value=name
 /label
Password/label
input type=password name=input1 id=input1 value=password
 /label
Password (confirm)/label
input type=password name=input2 id=input2 value=password
 /
Success (Registration name password)

Which looks correct to me. Your code looks fine to me as
well... Perhaps the error is not in the code you pasted, but somewhere
else. I am running on an older, and somewhat forked version of
Formlets, so there could also be a bug in the new code I
guess. Though, that seems unlikely. But it is worth noting that we are
not using the same version of the formlets library.

- jeremy

At Thu, 27 Aug 2009 16:09:18 +0100,
Colin Paul Adams wrote:
 
 I'm trying to validate user input against a database (using HaskellDB,
 but that doesn't seem to be the problem, as replacing the database
 monadic code with return True gives the same problem.
 
 This is part of my code:
 
 register :: Database - XForm Registration
 --register db = Registration $ pure_user * passConfirmed
 register db = Registration $ (user db) * passConfirmed
 
 user :: Database - XForm String
 user db = pure_user `F.checkM` F.ensureM valid error where
 valid name = do
   let q = do
 t - table user_table
 restrict (t!user_name .==. constant name)
 return t
   rs - query db q
   return $ null rs
 error = Username already exists in the database!
  
 pure_user :: XForm String
 pure_user = input `F.check` F.ensure valid error where
 input = Username `label` F.input Nothing
 valid = (= 3) . length
 error = Username must be three characters or longer.
 
 passConfirmed :: XForm String
 passConfirmed = fst $ passwords `F.check` F.ensure equal error where
 passwords = (,) $ pass Password * pass Password (confirm)
 equal (a, b) = a == b
 error = The entered passwords do not match!
 
 pass :: String - XForm String
 pass caption = input `F.check` F.ensure valid error where
 input = caption `label` F.password Nothing
 valid = (=6) . length
 error = Password must be six characters or longer.
 
 If I uncomment the commented line, and comment out the line after it
 (in register), then everything works as expected. However, using it as
 it is, one of the calls to pass gets the user's name for validation
 (and consequently either fails if the user name is only 5 characters,
 or the comparison of the two passwords fail (unless I type the user
 name as the password).
 
 I thought the applicative style meant the effects did not influence
 one another, but here there is clear contamination. What am i doing wrong?
 -- 
 Colin Adams
 Preston Lancashire
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe