{-# LANGUAGE QuasiQuotes, TypeFamilies, MultiParamTypeClasses, CPP #-} {-# LANGUAGE TemplateHaskell, FlexibleInstances, OverloadedStrings #-} -- | This module contains the yesod application and the views for the two examples. The -- angular javascript code is managed by StaticSettings.hs. module Main where import Data.Default (def) import Text.Cassius (cassiusFileReload) import Yesod import Yesod.EmbeddedStatic import Yesod.EmbeddedStatic.AngularJavascript import StaticSettings -- | Create a Yesod App which just has a static subsite. data MyApp = MyApp { getStatic :: EmbeddedStatic } mkYesod "MyApp" [parseRoutes| / HomeR GET /static StaticR EmbeddedStatic getStatic |] -- | A todo list. -- -- Angular's philosophy is that the view (the HTML defining the todo list) should be separate from -- the javascript controlling the todo list; the javascript should create a domain specific language -- (DSL) extending HTML in which the views can be written. Here inside the yesod handlers, we -- therefore create the view inside 'templates/todo.hamlet' and 'templates/todo.cassius' which take -- advantage of this DSL to create the todo list. Note that there is NO julius here; we are writing -- the view assuming the DSL has been defined. -- -- In general this should be how you design your applications: the views are Yesod widgets which you -- build up in your handlers, but these widgets should not have any attached javascript code. The -- javascript code should only be concerned with creating the DSL (irrespective of the views) and it -- should be managed separatly. todoList :: Widget --todoList = $(widgetFile "todo") -- In a scaffolded application, you would use $(widgetFile "todo") but widgetFile looks for the file -- "template/todo.hamlet". The problem is the templates are in "example/templates" because -- of the way we compile these examples, so widgetFile does not find the template. Therefore, we -- call whamletFile and cassiusFile directly. todoList = do toWidget $(cassiusFileReload "example/templates/todo.cassius") $(whamletFile "example/templates/todo.hamlet") -- | Another view, this time some tab pages which shows an example of using angular directives. -- -- Again, here inside the Yesod handlers we write the view assuming a DSL with two new tags: my-tabs -- and my-pane. There is no julius here, just the view HTML. tabExample :: Widget --tabExample = $(widgetFile "tab-example") tabExample = $(whamletFile "example/templates/tab-example.hamlet") -- | The Home Page -- -- To make our Angular DSL available, all that needs to happen is a reference to the -- Angular javascript files, which must be done via the ng_modules_example_js variable -- created by embedNgModule inside StaticSettings.hs. (You must use this route variable -- because during production it includes the ETag so that caching works properly.) getHomeR :: Handler Html getHomeR = defaultLayout $ do setTitle "Angular Example" -- Add the two javascript files addScript $ StaticR angular_js -- you might consider instead using angular from a CDN addScript $ StaticR ng_modules_example_js -- Add bootstrap addStylesheet $ StaticR bootstrap_min_css -- you might consider using a CDN instead [whamlet|

Todo List ^{todoList}

Directive Example ^{tabExample} |] instance Yesod MyApp where addStaticContent = embedStaticContent getStatic StaticR Right -- Create a MyApp using the EmbeddedStatic embStatic created inside StaticSettings.hs main :: IO () main = warp 3000 $ MyApp embStatic