mirror of
https://github.com/srid/ema.git
synced 2024-12-02 09:15:10 +03:00
Model-dependent static assets (#37)
* Have staticAssets take model as argument Make server lenient * FileSystem: allow ignoring patterns, eg: .git * Match tag in order * Fix ?== argument order * refactor
This commit is contained in:
parent
6492816d06
commit
edd49514bf
@ -37,7 +37,7 @@ runEmaPure ::
|
|||||||
(CLI.Action -> LByteString) ->
|
(CLI.Action -> LByteString) ->
|
||||||
IO ()
|
IO ()
|
||||||
runEmaPure render = do
|
runEmaPure render = do
|
||||||
runEma [] (const [()]) (\act () () -> render act) $ \model -> do
|
runEma (const []) (const $ one ()) (\act () () -> render act) $ \model -> do
|
||||||
LVar.set model ()
|
LVar.set model ()
|
||||||
liftIO $ threadDelay maxBound
|
liftIO $ threadDelay maxBound
|
||||||
|
|
||||||
@ -49,7 +49,7 @@ runEmaPure render = do
|
|||||||
runEma ::
|
runEma ::
|
||||||
forall model route.
|
forall model route.
|
||||||
(FileRoute route, Show route) =>
|
(FileRoute route, Show route) =>
|
||||||
[FilePath] ->
|
(model -> [FilePath]) ->
|
||||||
(model -> [route]) ->
|
(model -> [route]) ->
|
||||||
-- | How to render a route, given the model
|
-- | How to render a route, given the model
|
||||||
(CLI.Action -> model -> route -> LByteString) ->
|
(CLI.Action -> model -> route -> LByteString) ->
|
||||||
@ -68,7 +68,7 @@ runEmaWithCli ::
|
|||||||
forall model route.
|
forall model route.
|
||||||
(FileRoute route, Show route) =>
|
(FileRoute route, Show route) =>
|
||||||
Cli ->
|
Cli ->
|
||||||
[FilePath] ->
|
(model -> [FilePath]) ->
|
||||||
(model -> [route]) ->
|
(model -> [route]) ->
|
||||||
-- | How to render a route, given the model
|
-- | How to render a route, given the model
|
||||||
(CLI.Action -> model -> route -> LByteString) ->
|
(CLI.Action -> model -> route -> LByteString) ->
|
||||||
@ -103,7 +103,7 @@ runEmaWithCliInCwd ::
|
|||||||
-- or @Data.LVar.modify@ to modify it. Ema will automatically hot-reload your
|
-- or @Data.LVar.modify@ to modify it. Ema will automatically hot-reload your
|
||||||
-- site as this model data changes.
|
-- site as this model data changes.
|
||||||
LVar model ->
|
LVar model ->
|
||||||
[FilePath] ->
|
(model -> [FilePath]) ->
|
||||||
(model -> [route]) ->
|
(model -> [route]) ->
|
||||||
-- | Your site render function. Takes the current @model@ value, and the page
|
-- | Your site render function. Takes the current @model@ value, and the page
|
||||||
-- @route@ type as arguments. It must return the raw HTML to render to browser
|
-- @route@ type as arguments. It must return the raw HTML to render to browser
|
||||||
@ -114,8 +114,8 @@ runEmaWithCliInCwd cliAction model staticAssets staticRoutes render = do
|
|||||||
case cliAction of
|
case cliAction of
|
||||||
Generate dest -> do
|
Generate dest -> do
|
||||||
val <- LVar.get model
|
val <- LVar.get model
|
||||||
Generate.generate dest val staticAssets (staticRoutes val) (render cliAction)
|
Generate.generate dest val (staticAssets val) (staticRoutes val) (render cliAction)
|
||||||
Run -> do
|
Run -> do
|
||||||
void $ LVar.get model
|
void $ LVar.get model
|
||||||
port <- liftIO $ fromMaybe 8000 . (readMaybe @Int =<<) <$> lookupEnv "PORT"
|
port <- liftIO $ fromMaybe 8000 . (readMaybe @Int =<<) <$> lookupEnv "PORT"
|
||||||
Server.runServerWithWebSocketHotReload port model staticAssets (render cliAction)
|
Server.runServerWithWebSocketHotReload port model (render cliAction)
|
||||||
|
@ -42,6 +42,8 @@ generate dest model staticAssets routes render = do
|
|||||||
forM_ staticAssets $ \staticPath -> do
|
forM_ staticAssets $ \staticPath -> do
|
||||||
liftIO (doesPathExist staticPath) >>= \case
|
liftIO (doesPathExist staticPath) >>= \case
|
||||||
True ->
|
True ->
|
||||||
|
-- TODO: In current branch, we don't expect this to be a directory.
|
||||||
|
-- Although the user may pass it, but review before merge.
|
||||||
copyDirRecursively staticPath dest
|
copyDirRecursively staticPath dest
|
||||||
False ->
|
False ->
|
||||||
log LevelWarn $ toText $ "? " <> staticPath <> " (missing)"
|
log LevelWarn $ toText $ "? " <> staticPath <> " (missing)"
|
||||||
|
@ -35,8 +35,8 @@ import System.FSNotify
|
|||||||
withManager,
|
withManager,
|
||||||
)
|
)
|
||||||
import System.FilePath (isRelative, makeRelative)
|
import System.FilePath (isRelative, makeRelative)
|
||||||
import System.FilePattern (FilePattern, matchMany)
|
import System.FilePattern (FilePattern, matchMany, (?==))
|
||||||
import System.FilePattern.Directory (getDirectoryFiles)
|
import System.FilePattern.Directory (getDirectoryFilesIgnore)
|
||||||
import UnliftIO (MonadUnliftIO, toIO, withRunInIO)
|
import UnliftIO (MonadUnliftIO, toIO, withRunInIO)
|
||||||
|
|
||||||
-- | Mount the given directory on to the given LVar such that any filesystem
|
-- | Mount the given directory on to the given LVar such that any filesystem
|
||||||
@ -54,6 +54,8 @@ mountOnLVar ::
|
|||||||
FilePath ->
|
FilePath ->
|
||||||
-- | Only include these files (exclude everything else)
|
-- | Only include these files (exclude everything else)
|
||||||
[(b, FilePattern)] ->
|
[(b, FilePattern)] ->
|
||||||
|
-- | Ignore these patterns
|
||||||
|
[FilePattern] ->
|
||||||
-- | The `LVar` onto which to mount.
|
-- | The `LVar` onto which to mount.
|
||||||
--
|
--
|
||||||
-- NOTE: It must not be set already. Otherwise, the value will be overriden
|
-- NOTE: It must not be set already. Otherwise, the value will be overriden
|
||||||
@ -71,15 +73,18 @@ mountOnLVar ::
|
|||||||
-- If the action throws an exception, it will be logged and ignored.
|
-- If the action throws an exception, it will be logged and ignored.
|
||||||
([(b, [FilePath])] -> FileAction -> m (model -> model)) ->
|
([(b, [FilePath])] -> FileAction -> m (model -> model)) ->
|
||||||
m ()
|
m ()
|
||||||
mountOnLVar folder pats var var0 toAction' = do
|
mountOnLVar folder pats ignore var var0 toAction' = do
|
||||||
let toAction x = interceptExceptions id . toAction' x
|
let toAction x = interceptExceptions id . toAction' x
|
||||||
log LevelInfo $ "Mounting path " <> toText folder <> " (filter: " <> show pats <> ") onto LVar"
|
log LevelInfo $ "Mounting path " <> toText folder <> " (filter: " <> show pats <> ") onto LVar"
|
||||||
LVar.set var =<< do
|
LVar.set var =<< do
|
||||||
fs <- filesMatchingWithTag folder pats
|
fs <- filesMatchingWithTag folder pats ignore
|
||||||
initialAction <- toAction fs Update
|
initialAction <- toAction fs Update
|
||||||
pure $ initialAction var0
|
pure $ initialAction var0
|
||||||
onChange folder $ \fp change -> do
|
onChange folder $ \fp change -> do
|
||||||
whenJust (getTag pats fp) $ \tag -> do
|
-- TODO: Should refactor the ignore part to be integral to pats, and be part
|
||||||
|
-- of `getTag`
|
||||||
|
let shouldIgnore = any (?== fp) ignore
|
||||||
|
whenJust (guard (not shouldIgnore) >> getTag pats fp) $ \tag -> do
|
||||||
-- TODO: We should probably debounce and group frequently-firing events
|
-- TODO: We should probably debounce and group frequently-firing events
|
||||||
-- here, but do so such that `change` is the same for the events in the
|
-- here, but do so such that `change` is the same for the events in the
|
||||||
-- group.
|
-- group.
|
||||||
@ -98,17 +103,17 @@ mountOnLVar folder pats var var0 toAction' = do
|
|||||||
Right v ->
|
Right v ->
|
||||||
pure v
|
pure v
|
||||||
|
|
||||||
filesMatching :: (MonadIO m, MonadLogger m) => FilePath -> [FilePattern] -> m [FilePath]
|
filesMatching :: (MonadIO m, MonadLogger m) => FilePath -> [FilePattern] -> [FilePattern] -> m [FilePath]
|
||||||
filesMatching parent' pats = do
|
filesMatching parent' pats ignore = do
|
||||||
parent <- liftIO $ canonicalizePath parent'
|
parent <- liftIO $ canonicalizePath parent'
|
||||||
log LevelInfo $ toText $ "Traversing " <> parent <> " for files matching " <> show pats
|
log LevelInfo $ toText $ "Traversing " <> parent <> " for files matching " <> show pats <> ", ignoring " <> show ignore
|
||||||
liftIO $ getDirectoryFiles parent pats
|
liftIO $ getDirectoryFilesIgnore parent pats ignore
|
||||||
|
|
||||||
-- | Like `filesMatching` but with a tag associated with a pattern so as to be
|
-- | Like `filesMatching` but with a tag associated with a pattern so as to be
|
||||||
-- able to tell which pattern a resulting filepath is associated with.
|
-- able to tell which pattern a resulting filepath is associated with.
|
||||||
filesMatchingWithTag :: (MonadIO m, MonadLogger m, Ord b) => FilePath -> [(b, FilePattern)] -> m [(b, [FilePath])]
|
filesMatchingWithTag :: (MonadIO m, MonadLogger m, Ord b) => FilePath -> [(b, FilePattern)] -> [FilePattern] -> m [(b, [FilePath])]
|
||||||
filesMatchingWithTag parent' pats = do
|
filesMatchingWithTag parent' pats ignore = do
|
||||||
fs <- filesMatching parent' (snd <$> pats)
|
fs <- filesMatching parent' (snd <$> pats) ignore
|
||||||
let m = Map.fromListWith (<>) $
|
let m = Map.fromListWith (<>) $
|
||||||
flip mapMaybe fs $ \fp -> do
|
flip mapMaybe fs $ \fp -> do
|
||||||
tag <- getTag pats fp
|
tag <- getTag pats fp
|
||||||
@ -118,7 +123,10 @@ filesMatchingWithTag parent' pats = do
|
|||||||
getTag :: [(b, FilePattern)] -> FilePath -> Maybe b
|
getTag :: [(b, FilePattern)] -> FilePath -> Maybe b
|
||||||
getTag pats fp =
|
getTag pats fp =
|
||||||
let pull patterns =
|
let pull patterns =
|
||||||
fmap (\(x, (), _) -> x) $ listToMaybe $ matchMany patterns (one ((), fp))
|
listToMaybe $
|
||||||
|
flip mapMaybe patterns $ \(tag, pattern) -> do
|
||||||
|
guard $ pattern ?== fp
|
||||||
|
pure tag
|
||||||
in if isRelative fp
|
in if isRelative fp
|
||||||
then pull pats
|
then pull pats
|
||||||
else -- `fp` is an absolute path (because of use of symlinks), so let's
|
else -- `fp` is an absolute path (because of use of symlinks), so let's
|
||||||
|
@ -20,7 +20,6 @@ import qualified Network.Wai.Handler.WebSockets as WaiWs
|
|||||||
import qualified Network.Wai.Middleware.Static as Static
|
import qualified Network.Wai.Middleware.Static as Static
|
||||||
import Network.WebSockets (ConnectionException)
|
import Network.WebSockets (ConnectionException)
|
||||||
import qualified Network.WebSockets as WS
|
import qualified Network.WebSockets as WS
|
||||||
import Relude.Extra.Foldable1 (foldl1')
|
|
||||||
import Text.Printf (printf)
|
import Text.Printf (printf)
|
||||||
import UnliftIO (MonadUnliftIO)
|
import UnliftIO (MonadUnliftIO)
|
||||||
|
|
||||||
@ -34,10 +33,9 @@ runServerWithWebSocketHotReload ::
|
|||||||
) =>
|
) =>
|
||||||
Int ->
|
Int ->
|
||||||
LVar model ->
|
LVar model ->
|
||||||
[FilePath] ->
|
|
||||||
(model -> route -> LByteString) ->
|
(model -> route -> LByteString) ->
|
||||||
m ()
|
m ()
|
||||||
runServerWithWebSocketHotReload port model staticAssets render = do
|
runServerWithWebSocketHotReload port model render = do
|
||||||
let settings = Warp.setPort port Warp.defaultSettings
|
let settings = Warp.setPort port Warp.defaultSettings
|
||||||
logger <- askLoggerIO
|
logger <- askLoggerIO
|
||||||
|
|
||||||
@ -102,13 +100,8 @@ runServerWithWebSocketHotReload port model staticAssets render = do
|
|||||||
Left (err :: ConnectionException) -> do
|
Left (err :: ConnectionException) -> do
|
||||||
log LevelError $ "Websocket error: " <> show err
|
log LevelError $ "Websocket error: " <> show err
|
||||||
LVar.removeListener model subId
|
LVar.removeListener model subId
|
||||||
assetsMiddleware = do
|
assetsMiddleware =
|
||||||
case nonEmpty staticAssets of
|
Static.static
|
||||||
Nothing -> id
|
|
||||||
Just topLevelPaths ->
|
|
||||||
let assetPolicy :: Static.Policy =
|
|
||||||
foldl1' (Static.<|>) $ Static.hasPrefix <$> topLevelPaths
|
|
||||||
in Static.staticPolicy assetPolicy
|
|
||||||
httpApp logger req f = do
|
httpApp logger req f = do
|
||||||
flip runLoggingT logger $ do
|
flip runLoggingT logger $ do
|
||||||
let path = Wai.pathInfo req
|
let path = Wai.pathInfo req
|
||||||
|
Loading…
Reference in New Issue
Block a user