1
1
mirror of https://github.com/srid/ema.git synced 2024-11-29 09:25:14 +03:00

refactor Ema.Route

This commit is contained in:
Sridhar Ratnakumar 2021-04-19 15:34:10 -04:00
parent 7463e87a9c
commit 5c84eb10a6
7 changed files with 103 additions and 84 deletions

View File

@ -23,7 +23,7 @@ Open in VSCode, and run the build task.
## TODO
- [x] MVP
- [ ] Implement hot reload, and ditch browser-sync
- [x] Implement hot reload, and ditch browser-sync
- [x] server to client refresh
- [x] client to server reconnect (on ghcid reload, or accidental client disconnect)
- [x] or, investigate https://hackage.haskell.org/package/ghci-websockets

View File

@ -74,6 +74,8 @@ library
Ema.Example
Ema.Layout
Ema.Route
Ema.Route.Slug
Ema.Route.UrlStrategy
hs-source-dirs: src
default-language: Haskell2010

View File

@ -1,6 +1,7 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
-- | TODO: Refactor this module
module Ema.App where
import Control.Concurrent.Async (race_)

View File

@ -62,10 +62,9 @@ timeC = do
runSimpleSitePure :: IO ()
runSimpleSitePure = do
(model, runTimeC) <- timeC
race_ runTimeC (runEma $ ema model)
race_ runTimeC (runEma $ Ema model render)
where
ema model =
Ema model $ \now r ->
render now r =
Layout.tailwindSite (H.title "Simple Site") $
H.div ! A.class_ "container mx-auto" $ do
H.header ! A.class_ "text-4xl font-bold border-b-1" $ "Simple Site!"

View File

@ -1,25 +1,17 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE QuasiQuotes #-}
module Ema.Route where
module Ema.Route
( IsRoute (..),
Slug (unSlug),
)
where
import Data.Default (Default, def)
import qualified Data.Text as T
import System.FilePath (joinPath)
-- ---- [Slug] ----
newtype Slug = Slug {unSlug :: Text}
deriving (Eq)
instance IsString Slug where
fromString :: HasCallStack => String -> Slug
fromString (toText -> s) =
if "/" `T.isInfixOf` s
then error ("Slug cannot contain a slash: " <> s)
else Slug s
-- ---- [Route] ----
import Data.Default (def)
import Ema.Route.Slug (Slug (unSlug))
import Ema.Route.UrlStrategy
( routeFileWithStrategy,
routeUrlWithStrategy,
)
class IsRoute r where
-- | Determine the route for the given URL slug
@ -31,53 +23,16 @@ class IsRoute r where
-- | Relative URL to use in "href"
routeUrl :: r -> Text
routeUrl =
routeUrlWithStrategy def
routeUrlWithStrategy def . toSlug
-- | Relative file path to .html file correspondong to this route.
routeFile :: r -> FilePath
routeFile =
routeFileWithStrategy def
routeFileWithStrategy def . toSlug
-- The unit route is used for sites that have a single route, i.e. index.html.
instance IsRoute () where
fromSlug = \case
[] -> Just ()
_ -> Nothing
toSlug () = []
-- ---- [UrlStrategy] ----
data UrlStrategy
= UrlStrategy_FolderOnly
| -- | Pretty URLs without ugly .html ext or slash-suffix
UrlStrategy_HtmlOnlySansExt
deriving (Eq, Show, Ord)
instance Default UrlStrategy where
def = UrlStrategy_HtmlOnlySansExt
routeUrlWithStrategy :: IsRoute r => UrlStrategy -> r -> Text
routeUrlWithStrategy strat r =
case strat of
UrlStrategy_FolderOnly ->
"/" <> T.replace "index.html" "" (toText $ routeFile r)
UrlStrategy_HtmlOnlySansExt ->
-- FIXME: This should replace only at the end, not middle
let fp = toText (routeFile r)
in if
| "index.html" == fp ->
"/"
| "/index.html" `T.isSuffixOf` fp ->
"/" <> T.take (T.length fp - T.length "/index.html") fp
| ".html" `T.isSuffixOf` fp ->
"/" <> T.take (T.length fp - T.length ".html") fp
| otherwise ->
"/" <> fp
routeFileWithStrategy :: IsRoute r => UrlStrategy -> r -> FilePath
routeFileWithStrategy strat (toSlug -> slugs) =
case strat of
UrlStrategy_FolderOnly ->
joinPath $ fmap (toString . unSlug) slugs <> ["index.html"]
UrlStrategy_HtmlOnlySansExt ->
let (term :| (reverse -> parts)) = fromMaybe ("index" :| []) $ nonEmpty (reverse $ fmap unSlug slugs)
in joinPath $ fmap toString parts <> [toString term <> ".html"]

17
src/Ema/Route/Slug.hs Normal file
View File

@ -0,0 +1,17 @@
{-# LANGUAGE InstanceSigs #-}
module Ema.Route.Slug where
import qualified Data.Text as T
-- ---- [Slug] ----
newtype Slug = Slug {unSlug :: Text}
deriving (Eq)
instance IsString Slug where
fromString :: HasCallStack => String -> Slug
fromString (toText -> s) =
if "/" `T.isInfixOf` s
then error ("Slug cannot contain a slash: " <> s)
else Slug s

View File

@ -0,0 +1,45 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE QuasiQuotes #-}
module Ema.Route.UrlStrategy where
import Data.Default (Default, def)
import qualified Data.Text as T
import Ema.Route.Slug (Slug (unSlug))
import System.FilePath (joinPath)
data UrlStrategy
= UrlStrategy_FolderOnly
| -- | Pretty URLs without ugly .html ext or slash-suffix
UrlStrategy_HtmlOnlySansExt
deriving (Eq, Show, Ord)
instance Default UrlStrategy where
def = UrlStrategy_HtmlOnlySansExt
routeUrlWithStrategy :: UrlStrategy -> [Slug] -> Text
routeUrlWithStrategy strat slugs =
case strat of
UrlStrategy_FolderOnly ->
"/" <> T.replace "index.html" "" (toText $ routeFileWithStrategy strat slugs)
UrlStrategy_HtmlOnlySansExt ->
-- FIXME: This should replace only at the end, not middle
let fp = toText (routeFileWithStrategy strat slugs)
in if
| "index.html" == fp ->
"/"
| "/index.html" `T.isSuffixOf` fp ->
"/" <> T.take (T.length fp - T.length "/index.html") fp
| ".html" `T.isSuffixOf` fp ->
"/" <> T.take (T.length fp - T.length ".html") fp
| otherwise ->
"/" <> fp
routeFileWithStrategy :: UrlStrategy -> [Slug] -> FilePath
routeFileWithStrategy strat slugs =
case strat of
UrlStrategy_FolderOnly ->
joinPath $ fmap (toString . unSlug) slugs <> ["index.html"]
UrlStrategy_HtmlOnlySansExt ->
let (term :| (reverse -> parts)) = fromMaybe ("index" :| []) $ nonEmpty (reverse $ fmap unSlug slugs)
in joinPath $ fmap toString parts <> [toString term <> ".html"]