[Haskell-cafe] happstack file serving
Antoine Latter
aslatter at gmail.com
Tue Nov 1 17:34:19 CET 2011
Including list.
---------- Forwarded message ----------
From: Antoine Latter <aslatter at gmail.com>
Date: Tue, Nov 1, 2011 at 11:33 AM
Subject: Re: [Haskell-cafe] happstack file serving
To: Gary Klindt <gary.klindt at googlemail.com>
On Tue, Nov 1, 2011 at 11:24 AM, Gary Klindt <gary.klindt at googlemail.com> wrote:
> Hey Antoine,
>
> thank you for answering. Your strategy is quite similar to the one I prefer.
> I misunderstood the behaviour of serveDirectory. The problem with external
> javascript files is solved.
> The other problem I had, was, that the argument 'msum' is a list, which has
> elements with the same type, so I needed a conversion from
> m [Char] to m Response.
> In Happstack.Server.Response there is a function, which actually does that:
> flatten:
>
> module Main where
>
> import Happstack.Server
> import Control.Monad
>
> main :: IO ()
> main = simpleHTTP nullConf $
> msum [ flatten $ dir "ok" $ ok "jeahh!"
> , serveDirectory DisableBrowsing ["index.html"] "static" ]
>
I would likely write that particular example:
> dir "ok" $ ok $ toResponse "jeahh!"
I find it convenient to convert to a 'Response' as close to the
'bottom' of the stack as possible.
Antoine
More information about the Haskell-Cafe
mailing list