{-# LANGUAGE CPP, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, QuasiQuotes, TemplateHaskell, TypeFamilies, TypeSynonymInstances, FlexibleInstances #-} {- Define the web application's foundation, in the usual Yesod style. See a default Yesod app's comments for more details of each part. -} module Foundation where import Prelude #if !MIN_VERSION_base(4,8,0) import Control.Applicative ((<$>)) #endif import Data.IORef import Yesod import Yesod.Static import Yesod.Default.Config #ifndef DEVELOPMENT import Yesod.Default.Util (addStaticContentExternal) #endif import Network.HTTP.Conduit (Manager) -- import qualified Settings import Settings.Development (development) import Settings.StaticFiles import Settings (staticRoot, widgetFile, Extra (..)) #ifndef DEVELOPMENT import Settings (staticDir) import Text.Jasmine (minifym) #endif import Text.Blaze.Html.Renderer.String (renderHtml) import Text.Hamlet (hamletFile) import Hledger.Web.WebOptions import Hledger.Data.Types -- import Hledger.Web.Settings -- import Hledger.Web.Settings.StaticFiles -- for addform import Data.List import Data.Maybe import Data.Text as Text (Text,pack,unpack) import Data.Time.Calendar #if BLAZE_HTML_0_4 import Text.Blaze (preEscapedString, Markup) #else import Text.Blaze (Markup) import Text.Blaze.Internal (preEscapedString) #endif import Text.JSON import Hledger.Data.Journal import Hledger.Query import Hledger hiding (is) import Hledger.Cli hiding (version) -- | The site argument for your application. This can be a good place to -- keep settings and values requiring initialization before your application -- starts running, such as database connections. Every handler will have -- access to the data present here. data App = App { settings :: AppConfig DefaultEnv Extra , getStatic :: Static -- ^ Settings for static file serving. , httpManager :: Manager -- , appOpts :: WebOpts , appJournal :: IORef Journal } -- Set up i18n messages. See the message folder. mkMessage "App" "messages" "en" -- This is where we define all of the routes in our application. For a full -- explanation of the syntax, please see: -- http://www.yesodweb.com/book/handler -- -- This function does three things: -- -- * Creates the route datatype AppRoute. Every valid URL in your -- application can be represented as a value of this type. -- * Creates the associated type: -- type instance Route App = AppRoute -- * Creates the value resourcesApp which contains information on the -- resources declared below. This is used in Handler.hs by the call to -- mkYesodDispatch -- -- What this function does *not* do is create a YesodSite instance for -- App. Creating that instance requires all of the handler functions -- for our application to be in scope. However, the handler functions -- usually require access to the AppRoute datatype. Therefore, we -- split these actions into two functions and place them in separate files. mkYesodData "App" $(parseRoutesFile "config/routes") -- | A convenience alias. type AppRoute = Route App type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget) -- Please see the documentation for the Yesod typeclass. There are a number -- of settings which can be configured by overriding methods here. instance Yesod App where approot = ApprootMaster $ appRoot . settings -- -- Store session data on the client in encrypted cookies, -- -- default session idle timeout is 120 minutes -- makeSessionBackend _ = fmap Just $ defaultClientSessionBackend -- (120 * 60) -- ".hledger-web_client_session_key.aes" -- don't use session data makeSessionBackend _ = return Nothing defaultLayout widget = do master <- getYesod lastmsg <- getMessage vd@VD{..} <- getViewData -- We break up the default layout into two components: -- default-layout is the contents of the body tag, and -- default-layout-wrapper is the entire page. Since the final -- value passed to hamletToRepHtml cannot be a widget, this allows -- you to use normal widget features in default-layout. -- pc <- widgetToPageContent $ do -- $(widgetFile "normalize") -- addStylesheet $ StaticR css_bootstrap_css -- $(widgetFile "default-layout") -- hamletToRepHtml $(hamletFile "templates/default-layout-wrapper.hamlet") pc <- widgetToPageContent $ do addStylesheet $ StaticR css_bootstrap_min_css addStylesheet $ StaticR css_bootstrap_datepicker_standalone_min_css -- load these things early, in HEAD: toWidgetHead [hamlet| " "<\\/script>" -- #236 listToJsonValueObjArrayStr as = preEscapedString $ escapeJSSpecialChars $ encode $ JSArray $ map (\a -> JSObject $ toJSObject [("value", showJSON a)]) as numpostings = 4 postingnums = [1..numpostings] filepaths = map fst $ jfiles j postingfields :: ViewData -> Int -> HtmlUrl AppRoute postingfields _ n = [hamlet|
|] where acctvar = "account" ++ show n acctph = "Account " ++ show n amtvar = "amount" ++ show n amtph = "Amount " ++ show n grpvar = "grp" ++ show n journalselect :: [FilePath] -> HtmlUrl AppRoute journalselect journalfilepaths = [hamlet| |]