[web-devel] Happstack external js

Jeremy Shaw jeremy at n-heptane.com
Tue Jun 28 06:38:41 CEST 2011


Hello,

This is nothing fancy needed. You need two pieces:

  1. in the html you have the script tag reference an external file
  2. you use serveFile or serveDirectory to make that file accessible.  
Here is an example:

 > {-# LANGUAGE OverloadedStrings #-}
 > module Main where
 >
 > import Control.Monad (msum)
 > import Text.Blaze.Html4.Strict ((!), html, head, body, p, script)
 > import Text.Blaze.Html4.Strict.Attributes (src, type_)
 > import Happstack.Server hiding (body)
 > import Prelude hiding (head)
 >
 > main :: IO ()
 > main = simpleHTTP nullConf $ handler "/usr/share/javascript/jquery"
 >
 > handler :: FilePath -> ServerPart Response
 > handler jqueryPath =
 >     msum [ dir "jquery" $ serveDirectory DisableBrowsing []  
jqueryPath
 >          , nullDir >> page
 >          ]
 >
 > page :: ServerPart Response
 > page
 >     = ok $ toResponse $
 >            html $ do
 >              head $ do
 >                script ! type_ "text/javascript" ! src "/jquery/ 
jquery.js" $ ""
 >                script ! type_ "text/javascript" $ "$ 
(document).ready(function(){ alert('jquery was here.'); });"
 >              body $ p $ "javascript demo"

the line:

 > dir "jquery" $ serveDirectory DisableBrowsing [] jqueryPath

maps an query to the url /jquery/<file> to the file on the disk /usr/ 
share/javascript/jquery/<file>

which makes it easy to select between jquery.min.js, jquery.js, etc.

In the blaze html we just have:

 >                script ! type_ "text/javascript" ! src "/jquery/ 
jquery.js" $ ""

Obviously, there are many different ways to do almost the same thing.  
We could do something like:

  dir "jquery.js" $ serveFile (asContentType "text/javascript") "/usr/ 
share/javascript/jquery/jquery.js"

And in the script tag just have, src="/jquery.js".

Hope this helps. If you still have questions, feel free to ask.

- jeremy

On Jun 27, 2011, at 9:12 PM, Mister Asafe Ribeiro wrote:

> How do i include a external js file, such as jquery, using blaze  
> html in Happstack?
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel




More information about the web-devel mailing list