wai-app-static-3.1.6.3: WAI application for static serving

Safe HaskellNone
LanguageHaskell98

WaiAppStatic.Storage.Embedded

Contents

Synopsis

Basic

embeddedSettings :: [(FilePath, ByteString)] -> StaticSettings Source #

Serve the list of path/content pairs directly from memory.

Template Haskell

type Etag = Text Source #

An Etag is used to return 304 Not Modified responses so the client does not need to download resources a second time. Usually the etag is built from a hash of the content. To disable Etags, you can pass the empty string. This will cause the content to be redownloaded on every request.

data EmbeddableEntry Source #

Used at compile time to hold data about an entry to embed into the compiled executable.

Constructors

EmbeddableEntry 

Fields

  • eLocation :: Text

    The location where this resource should be served from. The location can contain forward slashes (/) to simulate directories, but must not end with a forward slash.

  • eMimeType :: MimeType

    The mime type.

  • eContent :: Either (Etag, ByteString) ExpQ

    The content itself. The content can be given as a tag and bytestring, in which case the content will be embedded directly into the execuatble. Alternatively, the content can be given as a template haskell expression returning IO (Etag, ByteString) in which case this action will be executed on every request to reload the content (this is useful for a debugging mode).

mkSettings :: IO [EmbeddableEntry] -> ExpQ Source #

Create a StaticSettings at compile time that embeds resources directly into the compiled executable. The embedded resources are precompressed (depending on mime type) so that during runtime the resource can be served very quickly.

Because of GHC Template Haskell stage restrictions, you must define the entries in a different module than where you create the StaticSettings. For example,

{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings #-}
module A (mkEmbedded) where

import WaiAppStatic.Storage.Embedded
import Crypto.Hash.MD5 (hashlazy)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Base64 as B64
import qualified Data.Text as T
import qualified Data.Text.Encoding as T

hash :: BL.ByteString -> T.Text
hash = T.take 8 . T.decodeUtf8 . B64.encode . hashlazy

mkEmbedded :: IO [EmbeddableEntry]
mkEmbedded = do
    file <- BL.readFile "test.css"
    let emb = EmbeddableEntry {
                  eLocation = "somedir/test.css"
                , eMimeType = "text/css"
                , eContent  = Left (hash file, file)
                }

    let reload = EmbeddableEntry {
                     eLocation = "anotherdir/test2.txt"
                   , eMimeType = "text/plain"
                   , eContent  = Right [| BL.readFile "test2.txt" >>= \c -> return (hash c, c) |]
                   }

    return [emb, reload]

The above mkEmbedded will be executed at compile time. It loads the contents of test.css and computes the hash of test.css for the etag. The content will be available at the URL somedir/test.css. Internally, embedApp below will attempt to compress the content at compile time. The compression will only happen if the compressed content is shorter than the original and the mime type is either text or javascript. If the content is compressed, at runtime the precomputed compressed content will be served with the appropriate HTTP header. If embedApp decides not to compress the content, it will be served directly.

Secondly, mkEmbedded creates a reloadable entry. This will be available at the URL anotherdir/test2.txt. Whenver a request comes in for anotherdir/test2.txt, the action inside the quasiquote in eContent will be executed. This will re-read the test2.txt file and recompute its hash.

Finally, here is a module which uses the above action to create a Application.

{-# LANGUAGE TemplateHaskell #-}
module B where

import A
import Network.Wai (Application)
import Network.Wai.Application.Static (staticApp)
import WaiAppStatic.Storage.Embedded
import Network.Wai.Handler.Warp (run)

myApp :: Application
myApp = staticApp $(mkSettings mkEmbedded)

main :: IO ()
main = run 3000 myApp