{-# LANGUAGE OverloadedStrings, TemplateHaskell, QuasiQuotes #-} -- | Integrate an AngularJS application written in Javascript into the static subsite. -- -- is a javascript web framework for enhancing HTML to provide -- dynamic web applications. This module integrates an AngularJS application written in pure -- javascript into a Yesod application. (As of January 2014, there is some experiemental -- development work on Fay bindings to AngularJS, but unfortunately it is not currently usable.) -- -- An AngularJS application consists of several pieces: -- -- * Javascript code consisting of controllers, directives, and services attached to Angular -- modules. The goal of this javascript is to produce a domain specific language extending HTML. -- 'embedNgModule' uses the static subsite to serve this javascript code, serving a minimized -- and compressed file during production and serving individual files during development. -- -- * Directive Templates. In Angular, directives should be the only components which manipulate the -- DOM. This can happen in the directive javascript code or through a directive HTML template. -- 'embedNgModule' supports templates written in Hamlet, converting the Hamlet to HTML at compile -- time before embedding the HTML into the generated javascript. -- -- * The View. In Angular, the view is written in the DSL extending HTML. Normal Yesod -- Handlers and Widgets work great for the view (so nothing needed from this module). Note that your -- Yesod Widgets will not have any julius or attached javascript code, the javascript is entirely -- managed by 'embedNgModule'. -- -- * Testing. Angular makes testing (both unit and end-to-end) easy. For unit and mid-level -- testing, the normal Angular test runner is the best. -- 'hamletTestTemplate' assists with integrating Hamlet directive templates into karma. -- For end2end testing, the "Test.WebDriver.Commands.Angular" module in the -- package works well. -- -- There is an -- -- in the source code which shows an application, unit testing with karma, and end2end -- testing with webdriver. module Yesod.EmbeddedStatic.AngularJavascript( -- * File Layout -- $filelayout -- ** Javascript -- $jsformat -- ** Directives -- $dirformat -- * Generators embedNgModule , embedNgModules -- * Custom Directive Template Processing , embedNgModuleWithoutTemplates , embedNgModulesWithoutTemplates , directiveTemplates , directiveTemplatesWithSettings , directiveWidget -- * Testing , hamletTestTemplate ) where import Control.Applicative import Control.Monad (forM, unless) import Data.Aeson (encode, decode, toJSON, Value) import Data.Default (def) import Data.List (isPrefixOf, sort) import Data.Monoid ((<>), mconcat) import Language.Haskell.TH import Network.Mime (MimeType) import System.Directory (getDirectoryContents, doesDirectoryExist, doesFileExist) import System.FilePath import Text.Blaze.Renderer.Text (renderMarkup) import Text.Julius import Text.Hamlet (HamletSettings, defaultHamletSettings, shamletFile) import Text.Hamlet.RT (parseHamletRT, renderHamletRT) import Yesod.Core.Widget (whamletFileWithSettings, WidgetT, whamlet) import Yesod.EmbeddedStatic.Generators import Yesod.EmbeddedStatic.Types import Yesod.EmbeddedStatic.AngularJsMangle import qualified Data.ByteString.Lazy as BL import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.IO as TL import qualified Data.Text.Lazy.Encoding as TL ------------------------------------------------------------------------------- -- Generator ------------------------------------------------------------------------------- loadModule :: FilePath -> IO ([FilePath], [FilePath], Value) -- (javascript files, hamlet files, module dependency) loadModule dir = do content <- getDirectoryContents dir let files = sort $ filter (\m -> takeExtension m == ".js") content let tmpls = sort $ filter (\m -> takeExtension m == ".hamlet") content deps <- if "module-deps.json" `elem` content then do ct <- BL.readFile $ dir "module-deps.json" case decode ct of Just x -> return x Nothing -> return $ toJSON ([] :: [String]) else return $ toJSON ([] :: [String]) return (files, tmpls, deps) procTemplate :: FilePath -> IO (String, TL.Text) procTemplate f = do ct <- TL.readFile f ham <- parseHamletRT defaultHamletSettings $ TL.unpack ct html <- renderHamletRT ham [] (\() _ -> error "No url allowed") let jsF = replaceExtension f ".js" e <- doesFileExist jsF unless e $ error $ "Unable to find " ++ jsF mid <- parseDirectiveFile jsF name <- case mid of Nothing -> error $ "Unable to find templateUrl in " ++ jsF Just (x, _) -> return x return (name, renderMarkup html) toCache :: [(String, TL.Text)] -> BL.ByteString toCache [] = BL.empty toCache ts = BL.concat $ [header] ++ concatMap go ts ++ [footer] where header = "module.run(['$templateCache', function($templateCache) {\n" footer = "}]);\n" go (name, html) = [ "$templateCache.put(" , encode name , "," , encode html , ");\n" ] productionModule :: Bool -> String -> FilePath -> (BL.ByteString -> IO BL.ByteString) -> IO BL.ByteString productionModule inclTempl name dir mini = do putStrLn $ "Building AngularJS module " ++ name ++ " (" ++ dir ++ ")" (files, tmpls, deps) <- loadModule dir ct <- mapM cleanupDIFile $ map (dir) files tCt <- if inclTempl then toCache <$> mapM procTemplate (map (dir) tmpls) else return BL.empty let fileCt = "(function(module) {" <> BL.concat ct <> tCt <> "})(angular.module(" <> encode name <> "," <> encode deps <> "));" mini fileCt develModule :: Bool -> String -> Location -> FilePath -> IO BL.ByteString develModule inclTempl name loc dir = do (jsFiles, tmpls, deps) <- loadModule dir let files = if inclTempl then jsFiles ++ tmpls else jsFiles let script = [julius| (function() { if (angular.isUndefined(window.yesod_devel_scripts)) { window.yesod_devel_scripts = {}; } /* We want to defer bootstrap until all scripts are loaded */ if (!/^NG_DEFER_BOOTSTRAP!/.test(window.name)) { window.name = "NG_DEFER_BOOTSTRAP!" + window.name; window.yesod_devel_check_loaded = function() { for (var key in window.yesod_devel_scripts) { if (!window.yesod_devel_scripts[key]) { /* Not loaded yet */ return; } } /* Everything has loaded, bootstrap can continue */ angular.resumeBootstrap(); }; } /* Create the module */ angular.module(#{toJSON name}, #{deps}); /* Figure out the full path of the current script */ var scripts = document.getElementsByTagName("script"), path; for (var i=0; i=0) { path = scripts[i].src; break; } } /* Add a script tag for each file in the module */ var files = #{toJSON files}; for (var i = 0; i < files.length; i++) { /* Add the script to the list of scripts to wait for */ window.yesod_devel_scripts[#{toJSON name} + "/" + files[i]] = false; var s = document.createElement("script"); s.type = "application/javascript"; s.src = path + "/" + files[i]; document.body.appendChild(s); } })(); |] return $ TL.encodeUtf8 $ renderJavascript $ script (error "No URL interpolation allowed") develExtraFiles :: [T.Text] -- ^ location -> String -- ^ module name -> FilePath -- ^ directory for module -> [T.Text] -- ^ incomming url to check -> IO (Maybe (MimeType, BL.ByteString)) develExtraFiles loc name dir paths | length paths == length loc + 1 && loc `isPrefixOf` paths = do let file = T.unpack (paths !! (length paths - 1)) full = dir file e <- doesFileExist full if e then do ct <- if takeExtension file == ".hamlet" then (\x -> toCache [x]) <$> procTemplate full else BL.readFile full let ct' = BL.concat [ "(function(module) { " , ct , "\n" , "window.yesod_devel_scripts[" , encode $ name file -- JSON encoded file includes the quotes , "] = true;\n" , "window.yesod_devel_check_loaded();\n" , "})(angular.module(" , encode name -- JSON encoded name includes the quotes , "));" ] return $ Just ("application/javascript", ct') else return Nothing | otherwise = return Nothing -- | An angular module entry ngEntry :: Bool -> String -> Location -> FilePath -> (BL.ByteString -> IO BL.ByteString) -> Entry ngEntry incTempl name loc dir mini = def { ebHaskellName = Just $ pathToName loc , ebLocation = loc , ebMimeType = "application/javascript" , ebProductionContent = productionModule incTempl name dir mini , ebDevelReload = [| develModule ($(litE $ integerL $ if incTempl then 1 else 0) == (1 :: Integer)) $(litE $ stringL name) $(litE $ stringL loc) $(litE $ stringL dir) |] , ebDevelExtraFiles = Just [| develExtraFiles (T.splitOn (T.pack "/") $ T.pack $(litE $ stringL loc)) $(litE $ stringL name) $(litE $ stringL dir) |] } -- | Embed the javascript and directive templates from a single directory into the static subsite as -- a single Angular module file. For this to work, the directive templates cannot use any hamlet -- variable interpolation. -- -- During development, each @.js@ file is served separately (with some code to define the @module@ -- variable) and at the location where the combined file would appear during production, a small -- script which just loads all the @.js@ files from the directory is served. This makes debugging -- much easier. -- -- This generator produces one variable definition of type @Route EmbeddedStatic@ which is named by -- passing the location through 'pathToName'. embedNgModule :: String -- ^ Angular module name -> Location -- ^ location within the static subsite for the resulting javascript file -> FilePath -- ^ directory on disk (relative to build directory/directory containing the .cabal file) -- which contains the contents of the module. -> (BL.ByteString -> IO BL.ByteString) -- ^ minimizer such as 'uglifyJs' or 'jasmine' to use during production. -> Generator embedNgModule name loc dir mini = return [ngEntry True name loc dir mini] -- | Embed multiple angular modules into the static subsite. -- -- All subdirectories within the given directory are assumed to be angular modules, and each -- subdirectory is embedded by calling 'embedNgModule' on it. The subdirectory name is used -- for the module name. The location for the module will be the location given to this generator -- combined with the subdirectory name and then @.js@. embedNgModules :: Location -- ^ directory location within the static subsite where the modules should appear -> FilePath -- ^ directory on disk (relative to build directory/directory containing the .cabal file) -- containing angular modules. -> (BL.ByteString -> IO BL.ByteString) -- ^ minimizer such as 'uglifyJs' or 'jasmine' to use during production. -> Generator embedNgModules = multi embedNgModule -- | Same as 'embedNgModule' but the directive templates are not included. Use this if your -- directive templates require variable/type safe route interpolation. Your directive templates -- should then instead be inserted into a @WidgetT site IO ()@ using 'directiveTemplates' and then -- embedded into the final page. embedNgModuleWithoutTemplates :: String -- ^ Angular module name -> Location -- ^ location within the static subsite for the resulting javascript file -> FilePath -- ^ directory on disk (relative to build directory/directory containing -- the .cabal file) which contains the contents of the module. -> (BL.ByteString -> IO BL.ByteString) -- ^ minimizer such as 'uglifyJs' or 'jasmine' to use during production. -> Generator embedNgModuleWithoutTemplates name loc dir mini = return [ngEntry False name loc dir mini] -- | Embed multiple angular modules without templates into the static subsite. -- All subdirectories within the given directory are assumed to be angular modules, and each -- subdirectory is embedded by calling 'embedNgModuleWithoutTemplates' on it. embedNgModulesWithoutTemplates :: Location -- ^ directory location within the static subsite where the modules should appear -> FilePath -- ^ directory on disk (relative to build directory/directory containing the .cabal file) -- containing angular modules. -> (BL.ByteString -> IO BL.ByteString) -- ^ minimizer such as 'uglifyJs' or 'jasmine' to use during production. -> Generator embedNgModulesWithoutTemplates = multi embedNgModuleWithoutTemplates -- | Multi-module helper multi :: (String -> Location -> FilePath -> (BL.ByteString -> IO BL.ByteString) -> Generator) -- ^ either 'embedAngularModule' or 'embedAngularModuleWithoutTemplates' -> Location -- ^ directory location within the static subsite where the modules should appear -> FilePath -- ^ directory on disk (relative to build directory/directory containing the .cabal file) -- containing angular modules. -> (BL.ByteString -> IO BL.ByteString) -- ^ minimizer such as 'uglifyJs' or 'jasmine' to use during production. -> Generator multi proc loc dir mini = do mods <- runIO $ getDirectoryContents dir let mods' = filter (\m -> not (null m) && head m /= '.') mods fmap concat . forM mods' $ \m -> do exists <- runIO $ doesDirectoryExist $ dir m if exists then proc m (loc (m ++ ".js")) (dir m) mini else return [] -- | Create a @'WidgetT' site IO ()@ which contains all the directive templates written in Hamlet -- from the passed in directory. This is only needed if you use -- 'embedNgModuleWithoutTemplates' because your directive templates use variable/url -- interpolation. The template will be inside a @\