dev:web: cleanup
This commit is contained in:
parent
d5b967834f
commit
0396725e71
@ -171,6 +171,7 @@ instance Yesod App where
|
||||
|
||||
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
|
||||
|
||||
-- XXX why disabled during development ? Affects ghci, ghcid, tests, #2139 ?
|
||||
#ifndef DEVELOPMENT
|
||||
-- This function creates static content files in the static folder
|
||||
-- and names them based on a hash of their content. This allows
|
||||
|
||||
@ -72,7 +72,7 @@ web opts j = do
|
||||
h = host_ opts
|
||||
p = port_ opts
|
||||
u = base_url_ opts
|
||||
staticRoot = T.pack <$> file_url_ opts
|
||||
staticRoot = T.pack <$> file_url_ opts -- XXX not used #2139
|
||||
appconfig = AppConfig{appEnv = Development
|
||||
,appHost = fromString h
|
||||
,appPort = p
|
||||
|
||||
@ -1,6 +1,5 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
|
||||
-- | Settings are centralized, as much as possible, into this file. This
|
||||
-- includes database connection settings, static file locations, etc.
|
||||
@ -16,7 +15,6 @@ import qualified Data.Text as T
|
||||
import Data.Yaml
|
||||
import Language.Haskell.TH.Syntax (Q, Exp)
|
||||
import Text.Hamlet
|
||||
import Text.Shakespeare.Text (st)
|
||||
import Yesod.Default.Config
|
||||
import Yesod.Default.Util
|
||||
|
||||
@ -55,28 +53,28 @@ defbaseurl host port =
|
||||
else
|
||||
"http://" ++ host ++ if port /= 80 then ":" ++ show port else ""
|
||||
|
||||
-- Static setting below. Changing these requires a recompile
|
||||
-- Static file settings. Changing these requires a recompile.
|
||||
|
||||
-- | The location of static files on your system. This is a file system
|
||||
-- path. The default value works properly with your scaffolded site.
|
||||
-- | The file path on your machine where static files can be found.
|
||||
-- StaticFiles.hs uses this (must be separate for TH reasons).
|
||||
staticDir :: FilePath
|
||||
staticDir = "static"
|
||||
|
||||
-- | The base URL for your static files. As you can see by the default
|
||||
-- | The base URL for static files. As you can see by the default
|
||||
-- value, this can simply be "static" appended to your application root.
|
||||
-- A powerful optimization can be serving static files from a separate
|
||||
-- domain name. This allows you to use a web server optimized for static
|
||||
-- files, more easily set expires and cache values, and avoid possibly
|
||||
-- costly transference of cookies on static files. For more information,
|
||||
-- please see:
|
||||
-- http://code.google.com/speed/page-speed/docs/request.html#ServeFromCookielessDomain
|
||||
-- costly transference of cookies on static files.
|
||||
--
|
||||
-- If you change the resource pattern for StaticR in Foundation.hs, you will
|
||||
-- have to make a corresponding change here.
|
||||
-- If you change the resource pattern for StaticR in Foundation.hs,
|
||||
-- (or staticDir above), you will have to make a corresponding change here.
|
||||
--
|
||||
-- To see how this value is used, see urlRenderOverride in Foundation.hs
|
||||
--
|
||||
-- XXX Does not respect --file-url #2139
|
||||
staticRoot :: AppConfig DefaultEnv Extra -> Text
|
||||
staticRoot conf = fromMaybe [st|#{appRoot conf}/static|] . extraStaticRoot $ appExtra conf
|
||||
staticRoot conf = fromMaybe (appRoot conf <> "/static") . extraStaticRoot $ appExtra conf
|
||||
|
||||
-- | Settings for 'widgetFile', such as which template languages to support and
|
||||
-- default Hamlet settings.
|
||||
|
||||
@ -67,9 +67,6 @@ import Hledger.Cli hiding (prognameandversion)
|
||||
runTests :: String -> [(String,String)] -> Journal -> YesodSpec App -> IO ()
|
||||
runTests testsdesc rawopts j tests = do
|
||||
wopts <- rawOptsToWebOpts $ mkRawOpts rawopts
|
||||
-- print $ host_ wopts
|
||||
-- print $ port_ wopts
|
||||
-- print $ base_url_ wopts
|
||||
let yconf = AppConfig{ -- :: AppConfig DefaultEnv Extra
|
||||
appEnv = Testing
|
||||
-- https://hackage.haskell.org/package/conduit-extra/docs/Data-Conduit-Network.html#t:HostPreference
|
||||
@ -78,7 +75,7 @@ runTests testsdesc rawopts j tests = do
|
||||
-- Test with the host and port from opts. XXX more fragile, can clash with a running instance ?
|
||||
,appHost = host_ wopts & fromString
|
||||
,appPort = port_ wopts
|
||||
,appRoot = base_url_ wopts & T.pack
|
||||
,appRoot = base_url_ wopts & T.pack -- XXX not sure this or extraStaticRoot get used
|
||||
,appExtra = Extra
|
||||
{ extraCopyright = ""
|
||||
, extraAnalytics = Nothing
|
||||
@ -156,12 +153,13 @@ hledgerWebTest = do
|
||||
bodyContains "href=\"https://base"
|
||||
bodyContains "src=\"https://base"
|
||||
|
||||
runTests "hledger-web with --base-url, --file-url"
|
||||
[("base-url","https://base"), ("file-url","https://files")] nulljournal $ do
|
||||
-- #2139
|
||||
-- runTests "hledger-web with --base-url, --file-url"
|
||||
-- [("base-url","https://base"), ("file-url","https://files")] nulljournal $ do
|
||||
|
||||
yit "static file hyperlinks respect --file-url, others respect --base-url" $ do
|
||||
get JournalR
|
||||
statusIs 200
|
||||
bodyContains "href=\"https://base"
|
||||
bodyContains "src=\"https://files"
|
||||
-- yit "static file hyperlinks respect --file-url, others respect --base-url" $ do
|
||||
-- get JournalR
|
||||
-- statusIs 200
|
||||
-- bodyContains "href=\"https://base"
|
||||
-- bodyContains "src=\"https://files"
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user