static: update sample-embed.hs and point the old embedded static to the new one
This commit is contained in:
parent
2ad3977712
commit
8e16fd2227
@ -35,7 +35,6 @@ module Yesod.Static
|
||||
-- * Smart constructor
|
||||
, static
|
||||
, staticDevel
|
||||
, embed
|
||||
-- * Combining CSS/JS
|
||||
-- $combining
|
||||
, combineStylesheets'
|
||||
@ -54,6 +53,8 @@ module Yesod.Static
|
||||
, publicFiles
|
||||
-- * Hashing
|
||||
, base64md5
|
||||
-- * Embed
|
||||
, embed
|
||||
#ifdef TEST_EXPORT
|
||||
, getFileListPieces
|
||||
#endif
|
||||
@ -134,8 +135,11 @@ staticDevel dir = do
|
||||
hashLookup <- cachedETagLookupDevel dir
|
||||
return $ Static $ webAppSettingsWithLookup (F.decodeString dir) hashLookup
|
||||
|
||||
-- | Produce a 'Static' based on embedding all of the static
|
||||
-- files' contents in the executable at compile time.
|
||||
-- | Produce a 'Static' based on embedding all of the static files' contents in the
|
||||
-- executable at compile time.
|
||||
--
|
||||
-- You should use "Yesod.EmbeddedStatic" instead, it is much more powerful.
|
||||
--
|
||||
-- Nota Bene: if you replace the scaffolded 'static' call in Settings/StaticFiles.hs
|
||||
-- you will need to change the scaffolded addStaticContent. Otherwise, some of your
|
||||
-- assets will be 404'ed. This is because by default yesod will generate compile those
|
||||
|
||||
@ -1,23 +1,42 @@
|
||||
{-# LANGUAGE QuasiQuotes, TypeFamilies, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
import Yesod.Static
|
||||
import Yesod.Dispatch
|
||||
{-# LANGUAGE TemplateHaskell, QuasiQuotes, TypeFamilies #-}
|
||||
-- | This embeds just a single file; it embeds the source code file
|
||||
-- \"sample-embed.hs\" from the current directory so when you compile,
|
||||
-- the sample-embed.hs file must be in the current directory.
|
||||
--
|
||||
-- Try toggling the development argument to 'mkEmbeddedStatic'. When the
|
||||
-- development argument is true the file \"sample-embed.hs\" is reloaded
|
||||
-- from disk on every request (try changing it after you start the server).
|
||||
-- When development is false, the contents are embedded and the sample-embed.hs
|
||||
-- file does not even need to be present during runtime.
|
||||
module Main where
|
||||
|
||||
import Yesod.Core
|
||||
import Network.Wai.Handler.Warp (run)
|
||||
import Yesod.EmbeddedStatic
|
||||
|
||||
staticFiles "."
|
||||
mkEmbeddedStatic False "eStatic" [embedFile "sample-embed.hs"]
|
||||
|
||||
data Sample = Sample
|
||||
getStatic _ = $(embed "tests")
|
||||
mkYesod "Sample" [parseRoutes|
|
||||
/ RootR GET
|
||||
/static StaticR Static getStatic
|
||||
-- The above will generate variables
|
||||
-- eStatic :: EmbeddedStatic
|
||||
-- sample_embed_hs :: Route EmbeddedStatic
|
||||
|
||||
data MyApp = MyApp { getStatic :: EmbeddedStatic }
|
||||
|
||||
mkYesod "MyApp" [parseRoutes|
|
||||
/ HomeR GET
|
||||
/static StaticR EmbeddedStatic getStatic
|
||||
|]
|
||||
instance Yesod Sample where approot _ = ""
|
||||
|
||||
getRootR = do
|
||||
redirectText RedirectPermanent "static"
|
||||
return ()
|
||||
instance Yesod MyApp where
|
||||
addStaticContent = embedStaticContent getStatic StaticR Right
|
||||
|
||||
main = toWaiApp Sample >>= run 3000
|
||||
getHomeR :: Handler Html
|
||||
getHomeR = defaultLayout $ do
|
||||
toWidget [julius|console.log("Hello World");|]
|
||||
[whamlet|
|
||||
<h1>Hello
|
||||
<p>Check the
|
||||
<a href=@{StaticR sample_embed_hs}>embedded file
|
||||
|]
|
||||
|
||||
main :: IO ()
|
||||
main = warp 3000 $ MyApp eStatic
|
||||
|
||||
@ -12,6 +12,8 @@ build-type: Simple
|
||||
homepage: http://www.yesodweb.com/
|
||||
description: Static file serving subsite for Yesod Web Framework.
|
||||
extra-source-files:
|
||||
sample.hs
|
||||
sample-embed.hs
|
||||
test/*.hs
|
||||
test/fs/bar/baz
|
||||
test/fs/tmp/ignored
|
||||
|
||||
Loading…
Reference in New Issue
Block a user