[web-devel] Multi sites with Yesod or WAI

Michael Snoyman michael at snoyman.com
Sun May 29 19:49:12 CEST 2011


On Sun, May 29, 2011 at 8:23 PM, Eric Schug <schugschug at gmail.com> 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



More information about the web-devel mailing list