{-# LANGUAGE OverloadedStrings, TemplateHaskell, QuasiQuotes #-}

-- | Integrate an AngularJS application written in Javascript into the static subsite.
--
-- <http://angularjs.org/ AngularJS> 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 <http://karma-runner.github.io karma> is the best.
-- 'hamletTestTemplate' assists with integrating Hamlet directive templates into karma.
-- For end2end testing, the "Test.WebDriver.Commands.Angular" module in the
-- <https://hackage.haskell.org/package/webdriver-angular webdriver-angular> package works well.
--
-- There is an
-- <https://bitbucket.org/wuzzeb/yesod-static-angular/src/tip/example?at=default example>
-- 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<scripts.length; i++) {
      if (scripts[i].src.indexOf(#{toJSON loc})>=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 @\<script type=\"text/ng-template\"
-- id=\"someid\"\>@, where the ID is found by parsing the javascript code for @templateUrl@. This
-- widget must be inside the tag which has the @ng-app@ attribute.
directiveTemplates :: FilePath -> ExpQ
directiveTemplates = directiveTemplatesWithSettings defaultHamletSettings

-- | Same as 'directiveTemplates' but allows you to specify the hamlet settings.
directiveTemplatesWithSettings :: HamletSettings -> FilePath -> ExpQ
directiveTemplatesWithSettings settings dir = do
    (jsfiles, _, _) <- runIO $ loadModule dir
    hamlets <- runIO $ parseDirectiveFiles dir jsfiles
    let lst = [ tupE [litE $ stringL i, whamletFileWithSettings settings f] | (i,f) <- hamlets ]
    [| mconcat $ map (uncurry directiveWidget) $(listE lst) |]

-- | Wrap a widget in a @\<script type=\"text/ng-template\" id=\"someid\"\>@ block.
directiveWidget :: T.Text -- ^ ID of the directive
                -> WidgetT site IO () -- ^ the body of the template
                -> WidgetT site IO ()
directiveWidget name w = [whamlet|
<script type="text/ng-template" ##{name}>
    ^{w}
|]

-------------------------------------------------------------------------------
-- Testing
-------------------------------------------------------------------------------

-- | Convert a hamlet file to javascript for unit testing.
--
-- When unit testing the Angular code, the javascript is executed directly (without any processing
-- by 'embedNgModule').  But for the directives to work, the Hamlet templates must still be
-- converted to javascript which inserts the template into the Angular @$templateCache@.  This
-- TH splice takes a path to a hamlet file and produces a 'BL.ByteString' which contains this
-- javascript.  Before unit testing the javascript code, this TH splice must be run on every
-- directive hamlet template.
--
-- If you use <http://karma-runner.github.io karma>, the 
-- <https://npmjs.org/package/karma-ng-hamlet2js-preprocessor karma-ng-hamlet2js-preprocessor>
-- does this automatically by using @runghc@ to run a small Haskell script which calls
-- 'hamletTestTemplate'.  The example application uses this karma preprocessor.
hamletTestTemplate :: FilePath -> ExpQ
hamletTestTemplate f = do
    let jsName = replaceExtension f "js"
    e <- runIO $ doesFileExist jsName
    if not e
        then [| error $ "Unable to find " ++ $(litE $ stringL jsName) |]
        else do
            mid <- runIO $ parseDirectiveFile jsName
            case mid of
                Nothing -> [| error $ "Unable to find template ID from " ++ $(litE $ stringL jsName) |]
                Just (i, hamletFile) ->
                    [| BL.concat 
                        [ TL.encodeUtf8 $ TL.pack "module.run(function($templateCache) {\n"
                        , TL.encodeUtf8 $ TL.pack "    $templateCache.put("
                        , encode ($(litE $ stringL i) :: String)
                        , TL.encodeUtf8 $ TL.pack ",\n"
                        , encode $ renderMarkup $(shamletFile hamletFile)
                        , TL.encodeUtf8 $ TL.pack "\n);});"
                        ]
                    |]

-- $filelayout
-- This Haskell module assists with the management of Angular modules.  Each Angular module
-- cooresponds to a directory where each controller\/directive\/service\/factory\/etc. is located in
-- separate files within this directory.  For example, you might have files @angular\/myctrl.js@,
-- @angular\/somedirective.js@, @angular\/myservice.js@, and so on.  Also, for each directive that
-- does not use an inline template, you should have the corresponding directive template in a file
-- with the same name as the javascript file but with a @hamlet@ extension (e.g.
-- @angular\/somedirective.hamlet@).  For larger applications, you can organize the Angular code into
-- multiple Angular modules by using one directory per module.

-- $jsformat
-- All files with a @.js@ extension in the given directory will be loaded.  Each javascript file
-- should be written to assume that a variable named @module@ is already defined and holds the
-- angular module.  For example,
--
-- >module.controller("MyController", function($scope) {
-- >    $scope.hello = "Hello, World!";
-- >});
--
-- When compiling for production, these @.js@ files will be concatenated, combined with the code
-- defining the @module@ variable, DI annotated, minified, compressed, and then embedded into the 
-- executable to be served from the given location.  That is, the following javascript will be
-- automatically created:
--
-- >(function(module) {
-- >
-- >module.controller("MyController", ["$scope", function($scope) {
-- >    $scope.hello = "Hello, world!";
-- >}]);
-- >
-- ><contents of all the other .js files>
-- ><optionally contents of the directive templates (see below)>
-- >
-- >})(angular.module("module-name", <contents of module-deps.json>));
--
-- Note the @module-deps.json@ file: if this file exists within the directory, it
-- will be parsed and used as the module dependencies (so therefore the contents should be a
-- list of strings).  If this file does not exist, an empty list of dependencies is used.
-- 
-- Note also the inline dependency injection annotation of the @$scope@ parameter.  When compiling
-- for production, before running the minimizer, the javascript is parsed and DI parameters are
-- annotated.  The arguments to the top-level call to @module.somefunction@ will be annotated.
-- Also, if the call is @module.directive@, the body of the factory function will be scanned for a
-- return of an object literal (must be an object literal, not a variable).  The object literal is
-- scanned for a @controller@ property, and if found that controller property is also DI annotated
-- (the example program shows this in action).



-- $dirformat
-- If a directive uses an external hamlet template, the directive hamlet and directive javascript
-- should be in two files with the same name but @.js@ and @.hamlet@ extensions.  To embed the
-- directive template so that the javascript is able to find it, the template ID must be loaded. To
-- do so, the javascript is parsed to find the value of @templateUrl@.  The @.js@ file must have a
-- top-level call to @module.directive@.  Some statement directly inside the factory function must
-- be a @return@ of an object literal.  This object literal must have a @templateUrl@ property with
-- a single string literal as the value.  This string literal is used as the ID when embedding the
-- template. For example, if @my-dialog.js@ contains
--
-- >module.directive("my-dialog", function() {
-- >    return {
-- >        restrict: "E",
-- >        transclude: true,
-- >        templateUrl: "mydialog-template",
-- >    };
-- >});
--
-- then something like the following will be automatically created and then inserted into the generated file:
--
-- >module.run(["$templateCache", function($templateCache) {
-- >    $templateCache.put("mydialog-template", <rendered my-dialog.hamlet>);
-- >}]);