{-# LANGUAGE OverloadedStrings #-} module Yesod.EmbeddedStatic.AngularJsMangle ( parseDirectiveFiles , parseDirectiveFile , cleanupDIFile ) where import Blaze.ByteString.Builder (toLazyByteString) import Control.Applicative import Data.Maybe (catMaybes) import Language.JavaScript.Parser import System.Directory (doesFileExist) import System.FilePath import qualified Data.ByteString.Lazy as BL ------------------------------------------------------------------------------- -- Dependency Injection Cleanup ------------------------------------------------------------------------------- -- | Parse the javascript file and convert all DI functions that rely on variable names to use -- inline annotation so that the javascript can be minimized. cleanupDIFile :: FilePath -> IO BL.ByteString cleanupDIFile f = toLazyByteString . renderJS . cleanupDI <$> parseFile f cleanupDI :: JSNode -> JSNode cleanupDI (NN (JSSourceElementsTop exprs)) = NN $ JSSourceElementsTop $ map diTopExpr exprs cleanupDI x = x diTopExpr :: JSNode -> JSNode diTopExpr (NN (JSExpression [ call@(NN (JSMemberDot [NT (JSIdentifier "module") _ _] _ -- Literal . (NT (JSIdentifier func) _ _))) -- function like controller/directive/etc. , NN (JSArguments open args close) ])) = NN $ JSExpression [call, NN $ JSArguments open (map (diFuncExpr directive) args) close] where directive = func == "directive" diTopExpr x = x -- | DI a single argument which is a function expression diFuncExpr :: Bool -> JSNode -> JSNode diFuncExpr isDir (NN (JSFunctionExpression a b c params d body)) = case params of [] -> func _ -> NN $ JSArrayLiteral aopen elems aclose where aopen = NT (JSLiteral "[") tokenPosnEmpty [NoComment] aclose = NT (JSLiteral "]") tokenPosnEmpty [NoComment] comma = NN (JSElision (NT (JSLiteral ",") tokenPosnEmpty [NoComment])) body' = if isDir then diBody body else body func = NN $ JSFunctionExpression a b c params d body' elems = map diParam params ++ [comma, func] diFuncExpr _ x = x -- | Convert a function parameter to a string literal and convert comma to elision diParam :: JSNode -> JSNode diParam (NT (JSIdentifier name) _ _) = NT (JSStringLiteral '"' name) tokenPosnEmpty [NoComment] diParam (NT (JSLiteral ",") _ _) = NN $ JSElision $ NT (JSLiteral ",") tokenPosnEmpty [NoComment] diParam x = x -- | Check a directive body to see if we need to DI cleanup a controller. diBody :: JSNode -> JSNode diBody (NN (JSBlock begin statements end)) = NN $ JSBlock begin (map diReturn statements) end diBody x = x -- | Check if a statement is a return of an object literal diReturn :: JSNode -> JSNode diReturn (NN (JSReturn ret [NN (JSExpression [NN (JSObjectLiteral begin props end)])] colon)) = NN $ JSReturn ret [NN (JSExpression [NN (JSObjectLiteral begin (map diProperty props) end)])] colon diReturn x = x testPropName :: String -> JSNode -> Bool testPropName n (NT (JSIdentifier n') _ _) = n == n' testPropName n (NT (JSStringLiteral _ n') _ _) = n == n' testPropName _ _ = False -- | Check a property of an object for controller diProperty :: JSNode -> JSNode diProperty (NN (JSPropertyNameandValue prop _ args)) | testPropName "controller" prop = NN $ JSPropertyNameandValue ctrl colon args' where ctrl = NT (JSStringLiteral '"' "controller") tokenPosnEmpty [NoComment] colon = NT (JSLiteral ":") tokenPosnEmpty [NoComment] args' = map (diFuncExpr False) args diProperty x = x ------------------------------------------------------------------------------- -- Loading directive IDs ------------------------------------------------------------------------------- -- | Parse all the javascript files. If the javascript file is a directive, -- the directive has a templateUrl, and there is a matching hamlet file, add the -- (id, hamlet file) into the return list. parseDirectiveFiles :: FilePath -> [FilePath] -> IO [(String,FilePath)] parseDirectiveFiles dir jsfiles = catMaybes <$> mapM parseDirectiveFile (map (dir) jsfiles) -- | Check a single javascript file to see if it is a directive parseDirectiveFile :: FilePath -> IO (Maybe (String, FilePath)) parseDirectiveFile f = do j <- parseFile f case parseDirId j of Nothing -> return Nothing Just i -> do let hamlet = replaceExtension f "hamlet" e <- doesFileExist hamlet if e then return $ Just (i, hamlet) else return Nothing firstJust :: [Maybe a] -> Maybe a firstJust [] = Nothing firstJust (x@(Just _):_) = x firstJust (Nothing:xs) = firstJust xs -- | Search for the directive ID parseDirId :: JSNode -> Maybe String parseDirId (NN (JSSourceElementsTop es)) = firstJust $ map parseDirectiveCall es parseDirId _ = Nothing -- | Parse module.directive(... function(..) { parseDirectiveCall :: JSNode -> Maybe String parseDirectiveCall (NN (JSExpression [NN (JSMemberDot [NT (JSIdentifier "module") _ _] _ -- Literal . (NT (JSIdentifier "directive") _ _)), NN (JSArguments _ args _)])) = firstJust $ map parseDirArg args parseDirectiveCall _ = Nothing -- | check the function argument to the directive call parseDirArg :: JSNode -> Maybe String parseDirArg (NN (JSFunctionExpression _ _ _ _ _ (NN (JSBlock _ statements _)))) = firstJust $ map parseDirSt statements parseDirArg _ = Nothing -- | Check a statement inside the factory function for return { .. }; parseDirSt :: JSNode -> Maybe String parseDirSt (NN (JSReturn _ [NN (JSExpression [NN (JSObjectLiteral _ props _)])] _)) = firstJust $ map parseDirTUrl props parseDirSt _ = Nothing -- | Check a property in the object literal parseDirTUrl :: JSNode -> Maybe String parseDirTUrl (NN (JSPropertyNameandValue prop _ [NT (JSStringLiteral _ tUrl) _ _])) | testPropName "templateUrl" prop = Just tUrl parseDirTUrl _ = Nothing