mirror of
https://github.com/srid/ema.git
synced 2024-12-01 23:23:42 +03:00
... fundeps no longer needed
Because ejecting staticRoutes also ejected the 'model' class argument
This commit is contained in:
parent
be9dfe6207
commit
494b90bf18
@ -48,7 +48,7 @@ runEmaPure render = do
|
||||
-- exits, and vice-versa.
|
||||
runEma ::
|
||||
forall model route.
|
||||
(Ema model route, Show route) =>
|
||||
(Ema route, Show route) =>
|
||||
(model -> [route]) ->
|
||||
-- | How to render a route, given the model
|
||||
(CLI.Action -> model -> route -> LByteString) ->
|
||||
@ -65,7 +65,7 @@ runEma staticRoutes render runModel = do
|
||||
-- Useful if you are handling CLI arguments yourself.
|
||||
runEmaWithCli ::
|
||||
forall model route.
|
||||
(Ema model route, Show route) =>
|
||||
(Ema route, Show route) =>
|
||||
Cli ->
|
||||
(model -> [route]) ->
|
||||
-- | How to render a route, given the model
|
||||
@ -91,7 +91,7 @@ runEmaWithCli cli staticRoutes render runModel = do
|
||||
-- | Run Ema live dev server
|
||||
runEmaWithCliInCwd ::
|
||||
forall model route m.
|
||||
(MonadEma m, Ema model route, Show route) =>
|
||||
(MonadEma m, Ema route, Show route) =>
|
||||
-- | CLI arguments
|
||||
CLI.Action ->
|
||||
-- | Your site model type, as a @LVar@ in order to support modifications over
|
||||
|
@ -1,6 +1,5 @@
|
||||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE DefaultSignatures #-}
|
||||
{-# LANGUAGE FunctionalDependencies #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
@ -17,7 +16,7 @@ type MonadEma m =
|
||||
)
|
||||
|
||||
-- | Enrich a model to work with Ema
|
||||
class Ema model route | route -> model where
|
||||
class Ema route where
|
||||
-- How to convert URLs to/from routes
|
||||
encodeRoute :: route -> [Slug]
|
||||
decodeRoute :: [Slug] -> Maybe route
|
||||
@ -29,7 +28,7 @@ class Ema model route | route -> model where
|
||||
staticAssets Proxy = mempty
|
||||
|
||||
-- | The unit model is useful when using Ema in pure fashion (see @Ema.runEmaPure@) with a single route (index.html) only.
|
||||
instance Ema () () where
|
||||
instance Ema () where
|
||||
encodeRoute () = []
|
||||
decodeRoute = \case
|
||||
[] -> Just ()
|
||||
|
@ -25,7 +25,7 @@ data Route
|
||||
|
||||
data Model = Model Text
|
||||
|
||||
instance Ema Model Route where
|
||||
instance Ema Route where
|
||||
encodeRoute = \case
|
||||
Index -> mempty
|
||||
About -> one "about"
|
||||
|
@ -25,7 +25,7 @@ data Route
|
||||
| OnlyTime
|
||||
deriving (Show, Enum, Bounded)
|
||||
|
||||
instance Ema UTCTime Route where
|
||||
instance Ema Route where
|
||||
encodeRoute = \case
|
||||
Index -> mempty
|
||||
OnlyTime -> one "time"
|
||||
|
@ -17,7 +17,7 @@ log = logWithoutLoc "Generate"
|
||||
|
||||
generate ::
|
||||
forall model route m.
|
||||
(MonadEma m, Ema model route) =>
|
||||
(MonadEma m, Ema route) =>
|
||||
FilePath ->
|
||||
model ->
|
||||
[route] ->
|
||||
@ -28,7 +28,7 @@ generate dest model routes render = do
|
||||
error $ "Destination does not exist: " <> toText dest
|
||||
log LevelInfo $ "Writing " <> show (length routes) <> " routes"
|
||||
forM_ routes $ \r -> do
|
||||
let fp = dest </> routeFile @model r
|
||||
let fp = dest </> routeFile r
|
||||
log LevelInfo $ toText $ "W " <> fp
|
||||
let !s = render model r
|
||||
liftIO $ do
|
||||
|
@ -24,10 +24,10 @@ import Ema.Route.UrlStrategy
|
||||
--
|
||||
-- As the returned URL is relative, you will have to either make it absolute (by
|
||||
-- prepending with `/`) or set the `<base>` URL in your HTML head element.
|
||||
routeUrl :: forall a r. Ema a r => r -> Text
|
||||
routeUrl :: forall r. Ema r => r -> Text
|
||||
routeUrl r =
|
||||
slugRelUrlWithStrategy def (encodeRoute @a r)
|
||||
slugRelUrlWithStrategy def (encodeRoute r)
|
||||
|
||||
routeFile :: forall a r. Ema a r => r -> FilePath
|
||||
routeFile :: forall r. Ema r => r -> FilePath
|
||||
routeFile r =
|
||||
slugFileWithStrategy def (encodeRoute @a r)
|
||||
slugFileWithStrategy def (encodeRoute r)
|
||||
|
@ -25,7 +25,7 @@ import Text.Printf (printf)
|
||||
|
||||
runServerWithWebSocketHotReload ::
|
||||
forall model route m.
|
||||
(Ema model route, Show route, MonadEma m) =>
|
||||
(Ema route, Show route, MonadEma m) =>
|
||||
Int ->
|
||||
LVar model ->
|
||||
(model -> route -> LByteString) ->
|
||||
@ -127,7 +127,7 @@ runServerWithWebSocketHotReload port model render = do
|
||||
<> show @Text err
|
||||
<> "</pre><p>Once you fix your code this page will automatically update.</body>"
|
||||
routeFromPathInfo =
|
||||
decodeRoute @model . fmap Slug.decodeSlug
|
||||
decodeRoute @route . fmap Slug.decodeSlug
|
||||
-- TODO: It would be good have this also get us the stack trace.
|
||||
unsafeCatch :: Exception e => a -> (e -> a) -> a
|
||||
unsafeCatch x f = unsafePerformIO $ catch (seq x $ pure x) (pure . f)
|
||||
|
Loading…
Reference in New Issue
Block a user