mirror of
https://github.com/srid/ema.git
synced 2024-11-25 20:12:20 +03:00
Add default implementation for staticRoutes
This commit is contained in:
parent
c0bc0da02a
commit
db68f1532d
@ -6,6 +6,7 @@
|
||||
- Add `Ord` instance to `Slug`
|
||||
- Helpers.Tailwind: add overflow-y-scroll to body
|
||||
- Add Ex03_Basic.hs example
|
||||
- Add default implementation based on Enum for `staticRoute`
|
||||
|
||||
## 0.1.0.0 -- 2021-04-26
|
||||
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE DefaultSignatures #-}
|
||||
{-# LANGUAGE FunctionalDependencies #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
@ -25,6 +26,8 @@ class Ema model route | route -> model where
|
||||
--
|
||||
-- This is never used by the dev server.
|
||||
staticRoutes :: model -> [route]
|
||||
default staticRoutes :: (Bounded route, Enum route) => model -> [route]
|
||||
staticRoutes _ = [minBound .. maxBound]
|
||||
|
||||
-- | List of (top-level) filepaths to serve as static assets
|
||||
--
|
||||
|
@ -1,5 +1,4 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
|
||||
-- | A very simple site with routes, but based on dynamically changing values
|
||||
--
|
||||
@ -11,7 +10,8 @@ module Ema.Example.Ex02_Basic where
|
||||
|
||||
import Control.Concurrent (threadDelay)
|
||||
import qualified Data.LVar as LVar
|
||||
import Ema (Ema (..), routeUrl, runEma)
|
||||
import Ema (Ema (..))
|
||||
import qualified Ema
|
||||
import qualified Ema.CLI
|
||||
import qualified Ema.Helper.Tailwind as Tailwind
|
||||
import Text.Blaze.Html5 ((!))
|
||||
@ -23,7 +23,9 @@ data Route
|
||||
| About
|
||||
deriving (Show, Enum, Bounded)
|
||||
|
||||
instance Ema () Route where
|
||||
data Model = Model Text
|
||||
|
||||
instance Ema Model Route where
|
||||
encodeRoute = \case
|
||||
Index -> mempty
|
||||
About -> one "about"
|
||||
@ -31,23 +33,21 @@ instance Ema () Route where
|
||||
[] -> Just Index
|
||||
["about"] -> Just About
|
||||
_ -> Nothing
|
||||
staticRoutes _ =
|
||||
[minBound .. maxBound]
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
runEma render $ \model ->
|
||||
forever $ do
|
||||
LVar.set model ()
|
||||
liftIO $ threadDelay maxBound
|
||||
Ema.runEma render $ \model -> do
|
||||
LVar.set model $ Model "Hello World. "
|
||||
liftIO $ threadDelay maxBound
|
||||
|
||||
render :: Ema.CLI.Action -> () -> Route -> LByteString
|
||||
render emaAction () r =
|
||||
render :: Ema.CLI.Action -> Model -> Route -> LByteString
|
||||
render emaAction (Model s) r =
|
||||
Tailwind.layout emaAction (H.title "Basic site") $
|
||||
H.div ! A.class_ "container mx-auto" $ do
|
||||
H.div ! A.class_ "mt-8 p-2 text-center" $ do
|
||||
case r of
|
||||
Index -> do
|
||||
H.toHtml s
|
||||
"You are on the index page. "
|
||||
routeElem About "Go to About"
|
||||
About -> do
|
||||
@ -57,4 +57,4 @@ render emaAction () r =
|
||||
routeElem r' w =
|
||||
H.a ! A.class_ "text-red-500 hover:underline" ! routeHref r' $ w
|
||||
routeHref r' =
|
||||
A.href (fromString . toString $ routeUrl r')
|
||||
A.href (fromString . toString $ Ema.routeUrl r')
|
@ -33,8 +33,6 @@ instance Ema UTCTime Route where
|
||||
[] -> Just Index
|
||||
["time"] -> Just OnlyTime
|
||||
_ -> Nothing
|
||||
staticRoutes _ =
|
||||
[minBound .. maxBound]
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
Loading…
Reference in New Issue
Block a user