Add a utility function, staticR, which can dynamically build StaticR routes with their ETags attached (still calculated at compile-time)
This commit is contained in:
parent
da82495fa2
commit
ddcca3104e
4 changed files with 49 additions and 0 deletions
25
src/Settings/StaticR/TH.hs
Normal file
25
src/Settings/StaticR/TH.hs
Normal file
|
@ -0,0 +1,25 @@
|
|||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
module Settings.StaticR.TH ( mkHashMap ) where
|
||||
|
||||
import Conduit hiding ( lift )
|
||||
import Data.List.Split ( splitOn )
|
||||
import Language.Haskell.TH.Syntax ( Q, Exp, lift, runIO )
|
||||
import Yesod.Static ( base64md5 )
|
||||
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
|
||||
base64md5File :: MonadIO m => FilePath -> m String
|
||||
base64md5File = fmap base64md5 . liftIO . L.readFile
|
||||
|
||||
genHashPair :: MonadIO m => FilePath -> m ([String], String)
|
||||
genHashPair fp = (tail $ splitOn "/" fp,) <$> base64md5File fp
|
||||
|
||||
genHashMap :: FilePath -> IO [([String], String)]
|
||||
genHashMap dir = runConduitRes
|
||||
$ sourceDirectoryDeep True dir
|
||||
.| mapMC genHashPair
|
||||
.| sinkList
|
||||
|
||||
mkHashMap :: FilePath -> Q Exp
|
||||
mkHashMap fp = lift =<< runIO (genHashMap fp)
|
Loading…
Add table
Add a link
Reference in a new issue