{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings, TypeFamilies #-} module AngularSpec where import Data.Monoid import RunGenerator import Test.HUnit import Test.Hspec import Text.Hamlet (xhtmlHamletSettings) import Yesod.Core import Yesod.EmbeddedStatic.AngularJavascript import Yesod.Test hiding (assertEqual) import qualified Data.ByteString.Lazy as BL ang1 :: GeneratorTestResult ang1 = head $(testGen (embedNgModuleWithoutTemplates "mod1" "a/b/c/def.js" "test/angular/mod1" (\x -> return $ x <> "\nAdded by mini") ) [("a/b/c/def.js", "application/javascript", "test/angular/mod1.js.expected")]) ang2s :: [GeneratorTestResult] ang2s = $(testGen (embedNgModulesWithoutTemplates "angmod" "test/angular" (\x -> return $ x <> "\nAdded by mini") ) [("angmod/mod1.js", "application/javascript", "test/angular/mod1.js.expected") ,("angmod/mod2.js", "application/javascript", "test/angular/mod2.js.expected") ]) ang3 :: GeneratorTestResult ang3 = head $(testGen (embedNgModule "mod1" "module1.js" "test/angular/mod1" (\x -> return $ x <> "\nAdded by mini") ) [("module1.js", "application/javascript", "test/angular/mod1-and-templ.js.expected")]) ang4s :: [GeneratorTestResult] ang4s = $(testGen (embedNgModules "xxx" "test/angular" (\x -> return $ x <> "\nAdded by mini") ) [("xxx/mod1.js", "application/javascript", "test/angular/mod1-and-templ.js.expected") ,("xxx/mod2.js", "application/javascript", "test/angular/mod2.js.expected") ]) data MyApp = MyApp mkYesod "MyApp" [parseRoutes| /single SingleWidgetR GET /files DirectiveFilesR GET /filesxhtml DirFilesXHTML GET |] instance Yesod MyApp getSingleWidgetR :: Handler Html getSingleWidgetR = defaultLayout $ do let direct = directiveWidget "mydirect" $(whamletFile "test/angular/mod1/my-tabs.hamlet") [whamlet|
^{direct}

Hello {{yourName}} |] getDirectiveFilesR :: Handler Html getDirectiveFilesR = defaultLayout $ do -- The hamlet files have
in them which should not be closed. let w = $(directiveTemplates "test/angular/mod1") [whamlet|
^{w}

Hello |] getDirFilesXHTML :: Handler Html getDirFilesXHTML = defaultLayout $ do -- The hamlet files have
in them which should be turned into
because of the xhtmlSettings let w = $(directiveTemplatesWithSettings xhtmlHamletSettings "test/angular/mod1") [whamlet|
^{w}

Hello |] spec :: Spec spec = do describe "Angular" $ do it "embeds a single module without templates" $ do maybe (return ()) assertFailure $ gtError ang1 assertDev ang1 "test/angular/ang1-mod1-dev.js.expected" assertDevExtra ang1 ["a","b","c","def.js","a.js"] "application/javascript" "test/angular/mod1/a-dev.js.expected" it "embeds multiple modules without templates" $ do case ang2s of [mod1, mod2] -> do maybe (return ()) assertFailure $ gtError mod1 maybe (return ()) assertFailure $ gtError mod2 assertDev mod1 "test/angular/ang2s-mod1-dev.js.expected" assertDev mod2 "test/angular/ang2s-mod2-dev.js.expected" assertDevExtra mod1 ["angmod","mod1.js","a.js"] "application/javascript" "test/angular/mod1/a-dev.js.expected" assertDevExtra mod2 ["angmod","mod2.js","ctrl.js"] "application/javascript" "test/angular/mod2/ctrl-dev.js.expected" _ -> assertFailure "did not create two modules" it "embeds a module together with templates" $ do maybe (return ()) assertFailure $ gtError ang3 assertDev ang3 "test/angular/ang3-mod1-and-templ-dev.js.expected" assertDevExtra ang3 ["module1.js", "my-tabs.hamlet"] "application/javascript" "test/angular/mod1/my-tabs-dev.js.expected" it "embeds multiple modules together with templates" $ do case ang4s of [mod1, mod2] -> do maybe (return ()) assertFailure $ gtError mod1 maybe (return ()) assertFailure $ gtError mod2 assertDev mod1 "test/angular/ang4s-mod1-and-templ-dev.js.expected" assertDev mod2 "test/angular/ang4s-mod2-dev.js.expected" assertDevExtra mod1 ["xxx","mod1.js","my-tabs.hamlet"] "application/javascript" "test/angular/mod1/my-tabs-dev.js.expected" assertDevExtra mod2 ["xxx","mod2.js","ctrl.js"] "application/javascript" "test/angular/mod2/ctrl-dev.js.expected" _ -> assertFailure "did not create two modules" it "generates the test template" $ do let testJs = $(hamletTestTemplate "test/angular/mod1/my-tabs.hamlet") testJs' <- BL.readFile "test/angular/mod1/my-tabs-testing.js.expected" assertEqual "my-tabs" testJs testJs' yesodSpec MyApp $ do yit "loads directive widget" $ do get SingleWidgetR statusIs 200 htmlCount "div[ng-app] > script[type=text/ng-template][id=mydirect]" 1 htmlAllContain "div[ng-app] > script[type=text/ng-template][id=mydirect]" "
  • " yit "loads directive files" $ do get DirectiveFilesR statusIs 200 -- This should use default settings so
    should not be closed htmlAllContain "div[ng-app] > script[type=text/ng-template][id=tabstemplateurl]" "
    \n
  • " -- Also br not closed here htmlAllContain "div[ng-app] > script[type=text/ng-template][id=paneid]" "
    \n
    " yit "loads directive files with settings" $ do get DirFilesXHTML statusIs 200 -- This should be identical to the previous test except the
    is closed now -- since we used XHTML settings htmlAllContain "div[ng-app] > script[type=text/ng-template][id=tabstemplateurl]" "
    \n
  • " -- Also br closed here htmlAllContain "div[ng-app] > script[type=text/ng-template][id=paneid]" "
    \n
    "