Wiki: markdown, chat subsite, event source

This example will tie together a few different ideas. We’ll start with a chat subsite, which allows us to embed a chat widget on any page. We’ll use the HTML 5 event source API to handle sending events from the server to the client.

  1. -- @Chat.hs
  2. {-# LANGUAGE OverloadedStrings, TypeFamilies, QuasiQuotes,
  3. TemplateHaskell, FlexibleInstances, MultiParamTypeClasses,
  4. FlexibleContexts
  5. #-}
  6. -- | This modules defines a subsite that allows you to insert a chat box on
  7. -- any page of your site. It uses eventsource for sending the messages from
  8. -- the server to the browser.
  9. module Chat where
  10. import Yesod
  11. import Control.Concurrent.Chan (Chan, dupChan, writeChan)
  12. import Data.Text (Text)
  13. import Network.Wai.EventSource (ServerEvent (..), eventSourceAppChan)
  14. import Language.Haskell.TH.Syntax (Type (VarT), Pred (ClassP), mkName)
  15. import Blaze.ByteString.Builder.Char.Utf8 (fromText)
  16. import Data.Monoid (mappend)
  17. -- | Our subsite foundation. We keep a channel of events that all connections
  18. -- will share.
  19. data Chat = Chat (Chan ServerEvent)
  20. -- | We need to know how to check if a user is logged in and how to get
  21. -- his/her username (for printing messages).
  22. class (Yesod master, RenderMessage master FormMessage)
  23. => YesodChat master where
  24. getUserName :: GHandler sub master Text
  25. isLoggedIn :: GHandler sub master Bool
  26. -- Now we set up our subsite. The first argument is the subsite, very similar
  27. -- to how we've used mkYesod in the past. The second argument is specific to
  28. -- subsites. What it means here is "the master site must be an instance of
  29. -- YesodChat".
  30. --
  31. -- We define two routes: a route for sending messages from the client to the
  32. -- server, and one for opening up the event stream to receive messages from
  33. -- the server.
  34. mkYesodSub "Chat"
  35. [ ClassP ''YesodChat [VarT $ mkName "master"]
  36. ] [parseRoutes|
  37. /send SendR POST
  38. /recv ReceiveR GET
  39. |]
  40. -- | Get a message from the user and send it to all listeners.
  41. postSendR :: YesodChat master => GHandler Chat master ()
  42. postSendR = do
  43. from <- getUserName
  44. -- Note that we're using GET parameters for simplicity of the Ajax code.
  45. -- This could easily be switched to POST. Nonetheless, our overall
  46. -- approach is still RESTful since this route can only be accessed via a
  47. -- POST request.
  48. body <- runInputGet $ ireq textField "message"
  49. -- Get the channel
  50. Chat chan <- getYesodSub
  51. -- Send an event to all listeners with the user's name and message.
  52. liftIO $ writeChan chan $ ServerEvent Nothing Nothing $ return $
  53. fromText from `mappend` fromText ": " `mappend` fromText body
  54. -- | Send an eventstream response with all messages streamed in.
  55. getReceiveR :: GHandler Chat master ()
  56. getReceiveR = do
  57. -- First we get the main channel
  58. Chat chan0 <- getYesodSub
  59. -- We duplicated the channel, which allows us to create broadcast
  60. -- channels.
  61. chan <- liftIO $ dupChan chan0
  62. -- Now we use the event source API. eventSourceAppChan takes two parameters:
  63. -- the channel of events to read from, and the WAI request. It returns a
  64. -- WAI response, which we can return with sendWaiResponse.
  65. req <- waiRequest
  66. res <- lift $ eventSourceAppChan chan req
  67. sendWaiResponse res
  68. -- | Provide a widget that the master site can embed on any page.
  69. chatWidget :: YesodChat master
  70. => (Route Chat -> Route master)
  71. -> GWidget sub master ()
  72. -- This toMaster argument tells us how to convert a Route Chat into a master
  73. -- route. You might think this is redundant information, but taking this
  74. -- approach means we can have multiple chat subsites in a single site.
  75. chatWidget toMaster = do
  76. -- Get some unique identifiers to help in creating our HTML/CSS. Remember,
  77. -- we have no idea what the master site's HTML will look like, so we
  78. -- should not assume we can make up identifiers that won't be reused.
  79. -- Also, it's possible that multiple chatWidgets could be embedded in the
  80. -- same page.
  81. chat <- lift newIdent -- the containing div
  82. output <- lift newIdent -- the box containing the messages
  83. input <- lift newIdent -- input field from the user
  84. ili <- lift isLoggedIn -- check if we're already logged in
  85. if ili
  86. then do
  87. -- Logged in: show the widget
  88. [whamlet|
  89. <div ##{chat}>
  90. <h2>Chat
  91. <div ##{output}>
  92. <input ##{input} type=text placeholder="Enter Message">
  93. |]
  94. -- Just some CSS
  95. toWidget [lucius|
  96. ##{chat} {
  97. position: absolute;
  98. top: 2em;
  99. right: 2em;
  100. }
  101. ##{output} {
  102. width: 200px;
  103. height: 300px;
  104. border: 1px solid #999;
  105. overflow: auto;
  106. }
  107. |]
  108. -- And now that Javascript
  109. toWidgetBody [julius|
  110. // Set up the receiving end
  111. var output = document.getElementById("#{output}");
  112. var src = new EventSource("@{toMaster ReceiveR}");
  113. src.onmessage = function(msg) {
  114. // This function will be called for each new message.
  115. var p = document.createElement("p");
  116. p.appendChild(document.createTextNode(msg.data));
  117. output.appendChild(p);
  118. // And now scroll down within the output div so the most recent message
  119. // is displayed.
  120. output.scrollTop = output.scrollHeight;
  121. };
  122. // Set up the sending end: send a message via Ajax whenever the user hits
  123. // enter.
  124. var input = document.getElementById("#{input}");
  125. input.onkeyup = function(event) {
  126. var keycode = (event.keyCode ? event.keyCode : event.which);
  127. if (keycode == '13') {
  128. var xhr = new XMLHttpRequest();
  129. var val = input.value;
  130. input.value = "";
  131. var params = "?message=" + encodeURI(val);
  132. xhr.open("POST", "@{toMaster SendR}" + params);
  133. xhr.send(null);
  134. }
  135. }
  136. |]
  137. else do
  138. -- User isn't logged in, give a not-logged-in message.
  139. master <- lift getYesod
  140. [whamlet|
  141. <p>
  142. You must be #
  143. $maybe ar <- authRoute master
  144. <a href=@{ar}>logged in
  145. $nothing
  146. logged in
  147. \ to chat.
  148. |]

This module stands on its own, and can be used in any application. Next we’ll provide such a driver application: a wiki. Our wiki will have a hard-coded homepage, and then a wiki section of the site. We’ll be using multiple dynamic pieces to allow an arbitrary hierarchy of pages within the Wiki.

For storage, we’ll just use a mutable reference to a Map. For a production application, this should be replaced with a proper database. The content will be stored and served as Markdown. yesod-auth‘s dummy plugin will provide us with (fake) authentication.

  1. {-# LANGUAGE OverloadedStrings, TypeFamilies, QuasiQuotes,
  2. TemplateHaskell, FlexibleInstances, MultiParamTypeClasses,
  3. FlexibleContexts
  4. #-}
  5. import Yesod
  6. import Yesod.Auth
  7. import Yesod.Auth.Dummy (authDummy)
  8. import Chat
  9. import Control.Concurrent.Chan (Chan, newChan)
  10. import Network.Wai.Handler.Warp (run)
  11. import Data.Text (Text)
  12. import qualified Data.Text.Lazy as TL
  13. import qualified Data.IORef as I
  14. import qualified Data.Map as Map
  15. import Text.Markdown (markdown, def)
  16. -- | Our foundation type has both the chat subsite and a mutable reference to
  17. -- a map of all our wiki contents. Note that the key is a list of Texts, since
  18. -- a wiki can have an arbitrary hierarchy.
  19. --
  20. -- In a real application, we would want to store this information in a
  21. -- database of some sort.
  22. data Wiki = Wiki
  23. { getChat :: Chat
  24. , wikiContent :: I.IORef (Map.Map [Text] Text)
  25. }
  26. -- Set up our routes as usual.
  27. mkYesod "Wiki" [parseRoutes|
  28. / RootR GET -- the homepage
  29. /wiki/*Texts WikiR GET POST -- note the multipiece for the wiki hierarchy
  30. /chat ChatR Chat getChat -- the chat subsite
  31. /auth AuthR Auth getAuth -- the auth subsite
  32. |]
  33. instance Yesod Wiki where
  34. authRoute _ = Just $ AuthR LoginR -- get a working login link
  35. -- Our custom defaultLayout will add the chat widget to every page.
  36. -- We'll also add login and logout links to the top.
  37. defaultLayout widget = do
  38. pc <- widgetToPageContent $ widget >> chatWidget ChatR
  39. mmsg <- getMessage
  40. hamletToRepHtml [hamlet|
  41. $doctype 5
  42. <html>
  43. <head>
  44. <title>#{pageTitle pc}
  45. ^{pageHead pc}
  46. <body>
  47. $maybe msg <- mmsg
  48. <div .message>#{msg}
  49. <nav>
  50. <a href=@{AuthR LoginR}>Login
  51. \ | #
  52. <a href=@{AuthR LogoutR}>Logout
  53. ^{pageBody pc}
  54. |]
  55. -- Fairly standard YesodAuth instance. We'll use the dummy plugin so that you
  56. -- can create any name you want, and store the login name as the AuthId.
  57. instance YesodAuth Wiki where
  58. type AuthId Wiki = Text
  59. authPlugins _ = [authDummy]
  60. loginDest _ = RootR
  61. logoutDest _ = RootR
  62. getAuthId = return . Just . credsIdent
  63. authHttpManager = error "authHttpManager" -- not used by authDummy
  64. -- Just implement authentication based on our yesod-auth usage.
  65. instance YesodChat Wiki where
  66. getUserName = requireAuthId
  67. isLoggedIn = do
  68. ma <- maybeAuthId
  69. return $ maybe False (const True) ma
  70. instance RenderMessage Wiki FormMessage where
  71. renderMessage _ _ = defaultFormMessage
  72. -- Nothing special here, just giving a link to the root of the wiki.
  73. getRootR :: Handler RepHtml
  74. getRootR = defaultLayout [whamlet|
  75. <p>Welcome to the Wiki!
  76. <p>
  77. <a href=@{wikiRoot}>Wiki root
  78. |]
  79. where
  80. wikiRoot = WikiR []
  81. -- A form for getting wiki content
  82. wikiForm mtext = renderDivs $ areq textareaField "Page body" mtext
  83. -- Show a wiki page and an edit form
  84. getWikiR :: [Text] -> Handler RepHtml
  85. getWikiR page = do
  86. -- Get the reference to the contents map
  87. icontent <- fmap wikiContent getYesod
  88. -- And read the map from inside the reference
  89. content <- liftIO $ I.readIORef icontent
  90. -- Lookup the contents of the current page, if available
  91. let mtext = Map.lookup page content
  92. -- Generate a form with the current contents as the default value.
  93. -- Note that we use the Textarea wrapper to get a <textarea>.
  94. (form, _) <- generateFormPost $ wikiForm $ fmap Textarea mtext
  95. defaultLayout $ do
  96. case mtext of
  97. -- We're treating the input as markdown. The markdown package
  98. -- automatically handles XSS protection for us.
  99. Just text -> toWidget $ markdown def $ TL.fromStrict text
  100. Nothing -> [whamlet|<p>Page does not yet exist|]
  101. [whamlet|
  102. <h2>Edit page
  103. <form method=post>
  104. ^{form}
  105. <div>
  106. <input type=submit>
  107. |]
  108. -- Get a submitted wiki page and updated the contents.
  109. postWikiR :: [Text] -> Handler RepHtml
  110. postWikiR page = do
  111. icontent <- fmap wikiContent getYesod
  112. content <- liftIO $ I.readIORef icontent
  113. let mtext = Map.lookup page content
  114. ((res, form), _) <- runFormPost $ wikiForm $ fmap Textarea mtext
  115. case res of
  116. FormSuccess (Textarea t) -> do
  117. liftIO $ I.atomicModifyIORef icontent $
  118. \m -> (Map.insert page t m, ())
  119. setMessage "Page updated"
  120. redirect $ WikiR page
  121. _ -> defaultLayout [whamlet|
  122. <form method=post>
  123. ^{form}
  124. <div>
  125. <input type=submit>
  126. |]
  127. main :: IO ()
  128. main = do
  129. -- Create our server event channel
  130. chan <- newChan
  131. -- Initially have a blank database of wiki pages
  132. icontent <- I.newIORef Map.empty
  133. -- Run our app
  134. warpDebug 3000 $ Wiki (Chat chan) icontent