Safe Haskell | None |
---|---|
Language | Haskell2010 |
A generator is executed at compile time to load a list of entries to embed into the subsite. This module contains several basic generators, but the design of generators and entries is such that it is straightforward to make custom generators for your own specific purposes, see this section.
Synopsis
- type Location = String
- embedFile :: FilePath -> Generator
- embedFileAt :: Location -> FilePath -> Generator
- embedDir :: FilePath -> Generator
- embedDirAt :: Location -> FilePath -> Generator
- concatFiles :: Location -> [FilePath] -> Generator
- concatFilesWith :: Location -> (ByteString -> IO ByteString) -> [FilePath] -> Generator
- jasmine :: ByteString -> IO ByteString
- uglifyJs :: ByteString -> IO ByteString
- yuiJavascript :: ByteString -> IO ByteString
- yuiCSS :: ByteString -> IO ByteString
- closureJs :: ByteString -> IO ByteString
- compressTool :: FilePath -> [String] -> ByteString -> IO ByteString
- tryCompressTools :: [ByteString -> IO ByteString] -> ByteString -> IO ByteString
- pathToName :: FilePath -> Name
Generators
type Location = String Source #
A location is a relative path within the static subsite at which resource(s) are made available. The location can include slashes to simulate directories but must not start or end with a slash.
embedFile :: FilePath -> Generator Source #
Embed a single file. Equivalent to passing the same string twice to embedFileAt
.
embedFileAt :: Location -> FilePath -> Generator Source #
Embed a single file at a given location within the static subsite and generate a
route variable based on the location via pathToName
. The FilePath
must be a relative
path to the directory in which you run cabal build
. During development, the file located
at this filepath will be reloaded on every request. When compiling for production, the contents
of the file will be embedded into the executable and so the file does not need to be
distributed along with the executable.
embedDir :: FilePath -> Generator Source #
Embed all files in a directory into the static subsite.
Equivalent to passing the empty string as the location to embedDirAt
,
so the directory path itself is not part of the resource locations (and so
also not part of the generated route variable names).
embedDirAt :: Location -> FilePath -> Generator Source #
Embed all files in a directory to a given location within the static subsite.
The directory tree rooted at the FilePath
(which must be relative to the directory in
which you run cabal build
) is embedded into the static subsite at the given
location. Also, route variables will be created based on the final location
of each file. For example, if a directory "static" contains the files
- css/bootstrap.css
- js/jquery.js
- js/bootstrap.js
then embedDirAt "somefolder" "static"
will
- Make the file
static/css/bootstrap.css
available at the locationsomefolder/css/bootstrap.css
within the static subsite and similarly for the other two files. - Create variables
somefolder_css_bootstrap_css
,somefolder_js_jquery_js
,somefolder_js_bootstrap_js
all of typeRoute EmbeddedStatic
. - During development, the files will be reloaded on every request. During production, the contents of all files will be embedded into the executable.
- During development, files that are added to the directory while the server
is running will not be detected. You need to recompile the module which
contains the call to
mkEmbeddedStatic
. This will also generate new route variables for the new files.
concatFiles :: Location -> [FilePath] -> Generator Source #
Concatinate a list of files and embed it at the location. Equivalent to passing return
to
concatFilesWith
.
concatFilesWith :: Location -> (ByteString -> IO ByteString) -> [FilePath] -> Generator Source #
Concatinate a list of files into a single ByteString
, run the resulting content through the given
function, embed it at the given location, and create a haskell variable name for the route based on
the location.
The processing function is only run when compiling for production, and the processing function is executed at compile time. During development, on every request the files listed are reloaded, concatenated, and served as a single resource at the given location without being processed.
Compression options for concatFilesWith
jasmine :: ByteString -> IO ByteString Source #
Convienient rexport of minifym
with a type signature to work with concatFilesWith
.
uglifyJs :: ByteString -> IO ByteString Source #
Use UglifyJS2 to compress javascript.
Assumes uglifyjs
is located in the path and uses options ["-m", "-c"]
to both mangle and compress and the option "-" to cause uglifyjs to read from
standard input.
yuiJavascript :: ByteString -> IO ByteString Source #
Use YUI Compressor to compress javascript.
Assumes a script yuicompressor
is located in the path. If not, you can still
use something like
compressTool "java" ["-jar", "/path/to/yuicompressor.jar", "--type", "js"]
yuiCSS :: ByteString -> IO ByteString Source #
Use YUI Compressor to compress CSS.
Assumes a script yuicompressor
is located in the path.
closureJs :: ByteString -> IO ByteString Source #
Use Closure to compress
javascript using the default options. Assumes a script closure
is located in
the path. If not, you can still run using
compressTool "java" ["-jar", "/path/to/compiler.jar"]
:: FilePath | program |
-> [String] | options |
-> ByteString | |
-> IO ByteString |
Helper to convert a process into a compression function. The process should be set up to take input from standard input and write to standard output.
tryCompressTools :: [ByteString -> IO ByteString] -> ByteString -> IO ByteString Source #
Try a list of processing functions (like the compressions above) one by one until one succeeds (does not raise an exception). Once a processing function succeeds, none of the remaining functions are used. If none succeeds, the input is just returned unprocessed. This is helpful if you are distributing code on hackage and do not know what compressors the user will have installed. You can list several and they will be tried in order until one succeeds.
Util
pathToName :: FilePath -> Name Source #
Clean up a path to make it a valid haskell name by replacing all non-letters and non-numbers by underscores. In addition, if the path starts with a capital letter or number add an initial underscore.
Custom Generators
Here is an example of creating your own custom generator. Because of template haskell stage restrictions, you must define generators in a different module from where you use them. The following generator will embed a JSON document that contains the compile time.
{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings #-} module CompileTime where import Data.Aeson import Data.Default import Data.Time import Yesod.EmbeddedStatic.Generators import Yesod.EmbeddedStatic.Types import qualified Data.ByteString.Lazy as BL getTime :: IO BL.ByteString getTime = do t <- getCurrentTime return $ encode $ object [ "compile_time" .= show t ] timeGenerator :: Location -> Generator timeGenerator loc = return $ [def { ebHaskellName = Just $ pathToName loc , ebLocation = loc , ebMimeType = "application/json" , ebProductionContent = getTime , ebDevelReload = [| getTime |] }]
Notice how the getTime
action is given as both ebProductionContent
and
ebDevelReload
. The result is that during development, the getTime
action
will be re-executed on every request so the time returned will be different
for each reload. When compiling for production, the getTime
action will
be executed once at compile time to produce the content to embed and never
called at runtime.
Here is a small example yesod program using this generator. Try toggling
the development argument to mkEmbeddedStatic
.
{-# LANGUAGE TemplateHaskell, QuasiQuotes, TypeFamilies #-} module Main where import Yesod import Yesod.EmbeddedStatic import CompileTime (timeGenerator) mkEmbeddedStatic True "eStatic" [timeGenerator "compile-time.json"] -- The above will generate variables -- eStatic :: EmbeddedStatic -- compile_time_json :: Route EmbeddedStatic data MyApp = MyApp { getStatic :: EmbeddedStatic } mkYesod "MyApp" [parseRoutes| / HomeR GET /static StaticR EmbeddedStatic getStatic |] instance Yesod MyApp getHomeR :: Handler Html getHomeR = defaultLayout $ [whamlet| <h1>Hello <p>Check the <a href=@{StaticR compile_time_json}>compile time |] main :: IO () main = warp 3000 $ MyApp eStatic