Problem with monadic formlets

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

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:
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

"Jeremy" == Jeremy Shaw
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

"Colin" == Colin Paul Adams
writes:
"Jeremy" == Jeremy Shaw
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

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
writes: "Jeremy" == Jeremy Shaw
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

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
writes: > "Jeremy" == Jeremy Shaw
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

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
participants (3)
-
Chris Eidhof
-
Colin Paul Adams
-
Jeremy Shaw