move #ifdef for static into StaticFiles

This commit is contained in:
Greg Weber 2011-08-24 22:16:59 -07:00
parent 8938401ce5
commit 06bda2877e
4 changed files with 14 additions and 9 deletions

View File

@ -10,7 +10,7 @@ module Application
import Foundation
import Settings
import Yesod.Static
import Settings.StaticFiles (static)
import Yesod.Auth
import Yesod.Logger (makeLogger, flushLogger, Logger, logString, logLazyText)
import Database.Persist.~importGenericDB~
@ -46,11 +46,7 @@ getRobotsR = return $ RepPlain $ toContent ("User-agent: *" :: ByteString)
-- migrations handled by Yesod.
with~sitearg~ :: AppConfig -> Logger -> (Application -> IO a) -> IO ()
with~sitearg~ conf logger f = do
#ifdef PRODUCTION
s <- static Settings.staticDir
#else
s <- staticDevel Settings.staticDir
#endif
Settings.withConnectionPool conf $ \p -> do
runConnectionPool (runMigration migrateAll) p
let h = ~sitearg~ conf logger s p

View File

@ -17,7 +17,7 @@ module Foundation
) where
import Yesod
import Yesod.Static
import Yesod.Static (Static, base64md5, StaticRoute(..))
import Settings.StaticFiles
import Yesod.Auth
import Yesod.Auth.OpenId
@ -177,7 +177,7 @@ instance YesodAuthEmail ~sitearg~ where
, partContent = Data.Text.Lazy.Encoding.encodeUtf8 [stext|
Please confirm your email address by clicking on the link below.
#{verurl}
\#{verurl}
Thank you
|]

View File

@ -1,7 +1,16 @@
{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies #-}
{-# LANGUAGE CPP, QuasiQuotes, TemplateHaskell, TypeFamilies #-}
module Settings.StaticFiles where
import Yesod.Static
import qualified Yesod.Static as Static
static :: FilePath -> IO Static
#ifdef PRODUCTION
static = Static.static
#else
static = Static.staticDevel
#endif
-- | This generates easy references to files in the static directory at compile time.
-- The upside to this is that you have compile-time verification that referenced files

View File

@ -14,7 +14,7 @@ module Foundation
) where
import Yesod.Core
import Yesod.Static
import Yesod.Static (Static, base64md5, StaticRoute(..))
import Settings.StaticFiles
import Yesod.Logger (Logger, logLazyText)
import qualified Settings