Hello,
I'm using the combination happstack + digestive-functors + web-routes + blazeHTML.
I'm not finding any examples on the net...
I've tried to adapt your example (thanks):
type NomicForm a = HappstackForm IO String BlazeFormHtml a
demoForm :: NomicForm (Text, Text)
demoForm =
(,) <$> ((TDB.label "greeting: " ++> inputNonEmpty Nothing) <* br)
<*> ((TDB.label "noun: " ++> inputNonEmpty Nothing) <* br)
<* (submit "submit")
where
br :: NomicForm ()
br = view H.br
-- make sure the fields are not blank, show errors in line if they are
inputNonEmpty :: Maybe Text -> NomicForm Text
inputNonEmpty v =
(inputText v `validate` (TD.check "You can not leave this field blank." (not . T.null)) <++ errors)
But I've got a problem on submit and inputText. I don't see how they are compatible with HappstackForm.
NomicForm a reduces to:
Form (ServerPartT IO) Input String BlazeFormHtml a
whereas the type of submit is:
submit :: Monad mYou said I need the latest happstack from darcs, why?
=> String -- ^ Text on the submit button
-> Form m String e BlazeFormHtml () -- ^ Submit button
Maybe I miss some instance?
BTW, I also tried to execute your exemple, but I can't install some packages.
> cabal install digestive-functors-hsp
cabal: Unknown build tool trhsx
Whereas trhsx is in my PATH (under linux).
Hello,
newRule also needs to have the type, RoutedNomicServer. The
transformation of RoutedNomicServer into NomicServer is done in the
handleSite function. Something like this:
nomicSpec :: ServerHandle -> Site Route (ServerPartT IO Response)
nomicSpec sh =
Site { handleSite = \f url -> unRouteT (nomicSite sh url) f
...
main =
do ...
simpleHTTP nullConf $ siteImpl (nomicSpec sh)
Or something like that -- it's hard to tell exactly what is going on
in your app based on the snippets you provided.
Also, I highly recommend using digestive functors instead of formlets.
It is the successor to formlets. Same core idea, better implementation
and actively maintained.
I have attached a quick demo of using:
happstack+digestive-functors+web-routes+HSP
To use it you will need the latest happstack from darcs plus:
hsp
web-routes
web-routes-hsp
web-routes-happstack
web-routes-mtl
digestive-functors
digestive-functors-hsp
I plan to clean up this example and document it better in the crash
course for the upcoming release. Clearly things like the FormInput
instance and the formPart function belong a library.
let me know if you have more questions.
- jeremy
On Sat, Jan 8, 2011 at 6:44 PM, Corentin Dupont
<corentin.dupont@gmail.com> wrote:
> Hello,
>
> I have difficulties mixing web-routes and forms:
> I have put routes in all my site, except for forms which remains with the
> type ServerPartT IO Response.
> How to make them work together?
>
> I have:
> type NomicServer = ServerPartT IO
> type RoutedNomicServer = RouteT PlayerCommand NomicServer
>
> newRule :: ServerHandle -> NomicServer Response
> newRule sh = do
> methodM POST -- only accept a post method
> mbEntry <- getData -- get the data
> case mbEntry of
> Nothing -> error $ "error: newRule"
> Just (NewRule name text code pn) -> do
> html <- nomicPageComm pn sh (submitRule name text code pn))
> ok $ toResponse html
>
>
> nomicPageComm :: PlayerNumber -> ServerHandle -> Comm () ->
> RoutedNomicServer Html
> nomicPageComm pn sh comm =
> (..)
>
>
> launchWebServer :: ServerHandle -> IO ()
> launchWebServer sh = do
> putStrLn "Starting web server...\nTo connect, drive your browser to
> \"http://localhost:8000/Login\""
> d <- liftIO getDataDir
> simpleHTTP nullConf $ mconcat [dir "postLogin" $ postLogin,
> fileServe [] d,
> dir "Login" $ ok $ toResponse $ loginPage,
> dir "NewRule" $ newRule sh,
> dir "NewGame" $ newGameWeb sh,
> dir "Nomic" $ do
> html <- implSite
> "http://localhost:8000/Nomic/" "" (nomicSite sh)
> ok $ toResponse html
> ]
>
>
> The red line doesn't compile. I don't know how to transform a
> RoutedNomicServer into a NomicServer.
>
> For the future I intend to use formlets: is these some examples of programs
> using happstack + web-routes + formlets?
>
> Thanks,
> Corentin
>
>
>
>
> On Fri, Jan 7, 2011 at 5:10 PM, Jeremy Shaw <jeremy@n-heptane.com> wrote:
>>
>> Hello,
>>
>> The [(String, String)] argument is for adding query parameters.
>>
>> > encodePathInfo ["foo", "bar", "baz"] [("key","value")]
>>
>> "foo/bar/baz?key=value"
>>
>> Instead of showURL you would use showURLParams.
>>
>> hope this helps!d
>> - jeremy
>>
>> On Fri, Jan 7, 2011 at 8:12 AM, Corentin Dupont
>> <corentin.dupont@gmail.com> wrote:
>> > Hello Jeremy,
>> > I'm using Web routes with happstack.
>> > I'm following this tutorial:
>> > http://tutorialpedia.org/tutorials/Happstack+type+safe+URLs.html
>> >
>> > But It seems out of synch with the latest version of web-routes: 0.23.2.
>> > The haddock documentation seems out of date also:
>> >
>> > encodePathInfo :: [String] -> [(String, String)] -> String
>> >
>> > For example:
>> >
>> > encodePathInfo [\"foo\", \"bar\", \"baz\"]
>> >
>> > "foo/bar/baz"
>> >
>> > And I can't figure out what this [(String, String)] is for ;)
>> >
>> > Thanks,
>> >
>> > Corentin
>> >
>
>