static: make Entry a setting type

In the future we might want to add new features to the
Entry.  I am currently thinking about source maps, where
a new field will need to be added to the Entry.  Therefore,
use Data.Default to make sure we don't need to bump the
major version for these features.
This commit is contained in:
John Lenz 2013-09-17 11:03:00 -05:00
parent 1a5aa23f13
commit 380cdcd174
3 changed files with 38 additions and 10 deletions

View File

@ -37,6 +37,7 @@ import Control.Monad.Trans.Resource (runResourceT)
import Data.Char (isDigit, isLower)
import Data.Conduit (($$), (=$))
import Data.Conduit.Process (proc, conduitProcess)
import Data.Default (def)
import Language.Haskell.TH
import Network.Mime (defaultMimeLookup)
import System.Directory (doesDirectoryExist, getDirectoryContents)
@ -61,13 +62,12 @@ embedFile f = embedFileAt f f
embedFileAt :: Location -> FilePath -> Generator
embedFileAt loc f = do
let mime = defaultMimeLookup $ T.pack f
let entry = Entry {
let entry = def {
ebHaskellName = Just $ pathToName loc
, ebLocation = loc
, ebMimeType = mime
, ebProductionContent = BL.readFile f
, ebDevelReload = [| BL.readFile $(litE $ stringL f) |]
, ebDevelExtraFiles = Nothing
}
return [entry]
@ -148,7 +148,12 @@ concatFilesWith loc process files = do
expFiles = listE $ map (litE . stringL) files
expCt = [| BL.concat <$> mapM BL.readFile $expFiles |]
mime = defaultMimeLookup $ T.pack loc
return [Entry (Just $ pathToName loc) loc mime load expCt Nothing]
return [def { ebHaskellName = Just $ pathToName loc
, ebLocation = loc
, ebMimeType = mime
, ebProductionContent = load
, ebDevelReload = expCt
}]
-- | Convienient rexport of 'minifym' with a type signature to work with 'concatFilesWith'.
jasmine :: BL.ByteString -> IO BL.ByteString
@ -242,6 +247,7 @@ pathToName f = routeName
-- >module CompileTime where
-- >
-- >import Data.Aeson
-- >import Data.Default
-- >import Data.Time
-- >import Yesod.EmbeddedStatic.Generators
-- >import Yesod.EmbeddedStatic.Types
@ -255,13 +261,12 @@ pathToName f = routeName
-- >
-- >timeGenerator :: Location -> Generator
-- >timeGenerator loc =
-- > return $ [Entry
-- > return $ [def
-- > { ebHaskellName = Just $ pathToName loc
-- > , ebLocation = loc
-- > , ebMimeType = "application/json"
-- > , ebProductionContent = getTime
-- > , ebDevelReload = [| getTime |]
-- > , ebDevelExtraFiles = Nothing
-- > }]
--
-- Notice how the @getTime@ action is given as both 'ebProductionContent' and

View File

@ -1,9 +1,18 @@
{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings #-}
module Yesod.EmbeddedStatic.Types(
Location
, Entry(..)
, Generator
-- ** Entry
, Entry
, ebHaskellName
, ebLocation
, ebMimeType
, ebProductionContent
, ebDevelReload
, ebDevelExtraFiles
) where
import Data.Default
import Language.Haskell.TH
import Network.Mime (MimeType)
import qualified Data.ByteString.Lazy as BL
@ -13,6 +22,9 @@ import qualified Data.ByteString.Lazy as BL
type Location = String
-- | A single resource embedded into the executable at compile time.
--
-- This data type is a settings type. For more information, see
-- <http://www.yesodweb.com/book/settings-types>.
data Entry = Entry {
ebHaskellName :: Maybe Name
-- ^ An optional haskell name. If the name is present, a variable
@ -41,5 +53,15 @@ data Entry = Entry {
-- and content.
}
-- | When using 'def', you must fill in at least 'ebLocation'.
instance Default Entry where
def = Entry { ebHaskellName = Nothing
, ebLocation = "xxxx"
, ebMimeType = "application/octet-stream"
, ebProductionContent = return BL.empty
, ebDevelReload = [| return BL.empty |]
, ebDevelExtraFiles = Nothing
}
-- | An embedded generator is executed at compile time to produce the entries to embed.
type Generator = Q [Entry]

View File

@ -1,6 +1,7 @@
{-# LANGUAGE TemplateHaskell, QuasiQuotes, OverloadedStrings #-}
module EmbedTestGenerator (testGen) where
import Data.Default
import Network.Mime (MimeType)
import Yesod.EmbeddedStatic.Types
import Yesod.EmbeddedStatic.Generators (pathToName)
@ -13,7 +14,7 @@ import qualified Data.ByteString.Lazy as BL
e1, e2, e3, e4 :: Entry
-- Basic entry
e1 = Entry
e1 = def
{ ebHaskellName = Just $ pathToName "e1"
, ebLocation = "e1"
, ebMimeType = "text/plain"
@ -23,7 +24,7 @@ e1 = Entry
}
-- Test simulated directory in location
e2 = Entry
e2 = def
{ ebHaskellName = Just $ pathToName "e2"
, ebLocation = "dir/e2"
, ebMimeType = "abcdef"
@ -33,7 +34,7 @@ e2 = Entry
}
-- Test empty haskell name
e3 = Entry
e3 = def
{ ebHaskellName = Nothing
, ebLocation = "xxxx/e3"
, ebMimeType = "yyy"
@ -48,7 +49,7 @@ devExtra ["dir", "dev2"] = return $ Just ("mime2", "dev2 content")
devExtra _ = return Nothing
-- Entry with devel extra files
e4 = Entry
e4 = def
{ ebHaskellName = Just $ pathToName "e4"
, ebLocation = "e4"
, ebMimeType = "text/plain"