
Is it possible to route applications based on the site name so that a single haskell process can support multiple sites with some shared data/applications? Is this handled at the WAI level or within Yesod? Eric

On Sun, May 29, 2011 at 8:23 PM, Eric Schug
Is it possible to route applications based on the site name so that a single haskell process can support multiple sites with some shared data/applications? Is this handled at the WAI level or within Yesod?
Eric
Another great question. This can be handled via the vhost middleware, at the WAI level. As before, here's the uncommented source, I'll try to get up a blogpost with more details later. Michael {-# LANGUAGE OverloadedStrings, QuasiQuotes, TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} import Yesod import Network.Wai.Middleware.Vhost import Network.Wai.Handler.Warp import Network.Wai data Site1 = Site1 data Site2 = Site2 data DefaultSite = DefaultSite mkYesod "Site1" [parseRoutes|/ Root1 GET|] getRoot1 = return $ RepPlain "Root1" mkYesod "Site2" [parseRoutes|/ Root2 GET|] getRoot2 = return $ RepPlain "Root2" mkYesod "DefaultSite" [parseRoutes|/ RootDef GET|] getRootDef = return $ RepPlain "RootDef" instance Yesod Site1 where approot _ = "" instance Yesod Site2 where approot _ = "" instance Yesod DefaultSite where approot _ = "" main = do app1 <- toWaiApp Site1 app2 <- toWaiApp Site2 appDef <- toWaiApp DefaultSite run 3000 $ vhost [ ((==) "host1" . serverName, app1) , ((==) "host2" . serverName, app2) ] appDef

Micheal, Looking at the pong.hs example for WAI gave me a possible clue. Replacing pathInfo with serverName, and paths with sitenames app req = return $ case pathInfo req of "/builder/withlen" -> builderWithLen "/builder/nolen" -> builderNoLen "/enum/withlen" -> enumWithLen "/enum/nolen" -> enumNoLen "/file/withlen" -> fileWithLen "/file/nolen" -> fileNoLen _ -> index $ pathInfo req but I like vhost method better. So with vhost can any boolean eval be used? First true is selected? Eric On 05/29/2011 01:49 PM, Michael Snoyman wrote:
On Sun, May 29, 2011 at 8:23 PM, Eric Schug
wrote: Is it possible to route applications based on the site name so that a single haskell process can support multiple sites with some shared data/applications? Is this handled at the WAI level or within Yesod?
Eric
Another great question. This can be handled via the vhost middleware, at the WAI level. As before, here's the uncommented source, I'll try to get up a blogpost with more details later.
Michael
{-# LANGUAGE OverloadedStrings, QuasiQuotes, TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import Yesod import Network.Wai.Middleware.Vhost import Network.Wai.Handler.Warp import Network.Wai
data Site1 = Site1 data Site2 = Site2 data DefaultSite = DefaultSite
mkYesod "Site1" [parseRoutes|/ Root1 GET|] getRoot1 = return $ RepPlain "Root1"
mkYesod "Site2" [parseRoutes|/ Root2 GET|] getRoot2 = return $ RepPlain "Root2"
mkYesod "DefaultSite" [parseRoutes|/ RootDef GET|] getRootDef = return $ RepPlain "RootDef"
instance Yesod Site1 where approot _ = "" instance Yesod Site2 where approot _ = "" instance Yesod DefaultSite where approot _ = ""
main = do app1<- toWaiApp Site1 app2<- toWaiApp Site2 appDef<- toWaiApp DefaultSite run 3000 $ vhost [ ((==) "host1" . serverName, app1) , ((==) "host2" . serverName, app2) ] appDef

Yes, precisely. vhost is actually very simple under the surface (most
of the middlewares are). If you're going to be implementing a large
number of virtual hosts, it will likely be more efficient to use
Data.Map on the serverName. But for a few hosts, it probably won't
make any significant difference.
Michael
On Sun, May 29, 2011 at 9:10 PM, Eric Schug
Micheal,
Looking at the pong.hs example for WAI gave me a possible clue. Replacing pathInfo with serverName, and paths with sitenames
app req = return $ case pathInfo req of "/builder/withlen" -> builderWithLen "/builder/nolen" -> builderNoLen "/enum/withlen" -> enumWithLen "/enum/nolen" -> enumNoLen "/file/withlen" -> fileWithLen "/file/nolen" -> fileNoLen _ -> index $ pathInfo req
but I like vhost method better. So with vhost can any boolean eval be used? First true is selected?
Eric
On 05/29/2011 01:49 PM, Michael Snoyman wrote:
On Sun, May 29, 2011 at 8:23 PM, Eric Schug
wrote: Is it possible to route applications based on the site name so that a single haskell process can support multiple sites with some shared data/applications? Is this handled at the WAI level or within Yesod?
Eric
Another great question. This can be handled via the vhost middleware, at the WAI level. As before, here's the uncommented source, I'll try to get up a blogpost with more details later.
Michael
{-# LANGUAGE OverloadedStrings, QuasiQuotes, TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import Yesod import Network.Wai.Middleware.Vhost import Network.Wai.Handler.Warp import Network.Wai
data Site1 = Site1 data Site2 = Site2 data DefaultSite = DefaultSite
mkYesod "Site1" [parseRoutes|/ Root1 GET|] getRoot1 = return $ RepPlain "Root1"
mkYesod "Site2" [parseRoutes|/ Root2 GET|] getRoot2 = return $ RepPlain "Root2"
mkYesod "DefaultSite" [parseRoutes|/ RootDef GET|] getRootDef = return $ RepPlain "RootDef"
instance Yesod Site1 where approot _ = "" instance Yesod Site2 where approot _ = "" instance Yesod DefaultSite where approot _ = ""
main = do app1<- toWaiApp Site1 app2<- toWaiApp Site2 appDef<- toWaiApp DefaultSite run 3000 $ vhost [ ((==) "host1" . serverName, app1) , ((==) "host2" . serverName, app2) ] appDef

Just to back that up, the code I was thinking of is:
main = do
app1 <- toWaiApp Site1
app2 <- toWaiApp Site2
appDef <- toWaiApp DefaultSite
let sites = Map.fromList
[ ("host1", app1)
, ("host2", app2)
]
run 3000 $ \req ->
case Map.lookup (serverName req) sites of
Nothing -> appDef req
Just app -> app req
Michael
On Sun, May 29, 2011 at 9:22 PM, Michael Snoyman
Yes, precisely. vhost is actually very simple under the surface (most of the middlewares are). If you're going to be implementing a large number of virtual hosts, it will likely be more efficient to use Data.Map on the serverName. But for a few hosts, it probably won't make any significant difference.
Michael
On Sun, May 29, 2011 at 9:10 PM, Eric Schug
wrote: Micheal,
Looking at the pong.hs example for WAI gave me a possible clue. Replacing pathInfo with serverName, and paths with sitenames
app req = return $ case pathInfo req of "/builder/withlen" -> builderWithLen "/builder/nolen" -> builderNoLen "/enum/withlen" -> enumWithLen "/enum/nolen" -> enumNoLen "/file/withlen" -> fileWithLen "/file/nolen" -> fileNoLen _ -> index $ pathInfo req
but I like vhost method better. So with vhost can any boolean eval be used? First true is selected?
Eric
On 05/29/2011 01:49 PM, Michael Snoyman wrote:
On Sun, May 29, 2011 at 8:23 PM, Eric Schug
wrote: Is it possible to route applications based on the site name so that a single haskell process can support multiple sites with some shared data/applications? Is this handled at the WAI level or within Yesod?
Eric
Another great question. This can be handled via the vhost middleware, at the WAI level. As before, here's the uncommented source, I'll try to get up a blogpost with more details later.
Michael
{-# LANGUAGE OverloadedStrings, QuasiQuotes, TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import Yesod import Network.Wai.Middleware.Vhost import Network.Wai.Handler.Warp import Network.Wai
data Site1 = Site1 data Site2 = Site2 data DefaultSite = DefaultSite
mkYesod "Site1" [parseRoutes|/ Root1 GET|] getRoot1 = return $ RepPlain "Root1"
mkYesod "Site2" [parseRoutes|/ Root2 GET|] getRoot2 = return $ RepPlain "Root2"
mkYesod "DefaultSite" [parseRoutes|/ RootDef GET|] getRootDef = return $ RepPlain "RootDef"
instance Yesod Site1 where approot _ = "" instance Yesod Site2 where approot _ = "" instance Yesod DefaultSite where approot _ = ""
main = do app1<- toWaiApp Site1 app2<- toWaiApp Site2 appDef<- toWaiApp DefaultSite run 3000 $ vhost [ ((==) "host1" . serverName, app1) , ((==) "host2" . serverName, app2) ] appDef
participants (2)
-
Eric Schug
-
Michael Snoyman