diff --git a/ema.cabal b/ema.cabal
index 4dec6b8..46f1fee 100644
--- a/ema.cabal
+++ b/ema.cabal
@@ -115,7 +115,6 @@ library
Ema.Generate
Ema.Route
Ema.Route.Slug
- Ema.Route.UrlStrategy
Ema.Server
if flag(with-examples)
diff --git a/src/Ema/Example/Ex02_Basic.hs b/src/Ema/Example/Ex02_Basic.hs
index fadb7b7..7cec0df 100644
--- a/src/Ema/Example/Ex02_Basic.hs
+++ b/src/Ema/Example/Ex02_Basic.hs
@@ -26,13 +26,13 @@ data Route
data Model = Model Text
instance FileRoute Route where
- encodeRoute =
- Ema.htmlSlugs . \case
- Index -> mempty
- About -> one "about"
- decodeRoute = \case
- [] -> Just Index
- ["about"] -> Just About
+ encodeFileRoute =
+ \case
+ Index -> "index.html"
+ About -> "about.html"
+ decodeFileRoute = \case
+ "index.html" -> Just Index
+ "about.html" -> Just About
_ -> Nothing
main :: IO ()
diff --git a/src/Ema/Example/Ex03_Clock.hs b/src/Ema/Example/Ex03_Clock.hs
index 87291a3..864feb4 100644
--- a/src/Ema/Example/Ex03_Clock.hs
+++ b/src/Ema/Example/Ex03_Clock.hs
@@ -27,13 +27,12 @@ data Route
deriving (Show, Enum, Bounded)
instance FileRoute Route where
- encodeRoute =
- Ema.htmlSlugs . \case
- Index -> mempty
- OnlyTime -> one "time"
- decodeRoute = \case
- [] -> Just Index
- ["time"] -> Just OnlyTime
+ encodeFileRoute = \case
+ Index -> "index.html"
+ OnlyTime -> "time.html"
+ decodeFileRoute = \case
+ "index.html" -> Just Index
+ "time.html" -> Just OnlyTime
_ -> Nothing
main :: IO ()
diff --git a/src/Ema/Generate.hs b/src/Ema/Generate.hs
index f075d27..8350126 100644
--- a/src/Ema/Generate.hs
+++ b/src/Ema/Generate.hs
@@ -6,7 +6,7 @@ module Ema.Generate where
import Control.Exception (throw)
import Control.Monad.Logger
-import Ema.Route (FileRoute, routeFile)
+import Ema.Route (FileRoute (encodeFileRoute))
import System.Directory (copyFile, createDirectoryIfMissing, doesDirectoryExist, doesFileExist, doesPathExist)
import System.FilePath (takeDirectory, (>))
import System.FilePattern.Directory (getDirectoryFiles)
@@ -33,7 +33,7 @@ generate dest model staticAssets 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 r
+ let fp = dest > encodeFileRoute r
log LevelInfo $ toText $ "W " <> fp
let !s = render model r
liftIO $ do
diff --git a/src/Ema/Helper/FileSystem.hs b/src/Ema/Helper/FileSystem.hs
index 6daadf1..ad554ee 100644
--- a/src/Ema/Helper/FileSystem.hs
+++ b/src/Ema/Helper/FileSystem.hs
@@ -35,7 +35,7 @@ import System.FSNotify
withManager,
)
import System.FilePath (isRelative, makeRelative)
-import System.FilePattern (FilePattern, matchMany, (?==))
+import System.FilePattern (FilePattern, (?==))
import System.FilePattern.Directory (getDirectoryFilesIgnore)
import UnliftIO (MonadUnliftIO, toIO, withRunInIO)
diff --git a/src/Ema/Route.hs b/src/Ema/Route.hs
index 5dba6d3..b72181e 100644
--- a/src/Ema/Route.hs
+++ b/src/Ema/Route.hs
@@ -3,52 +3,66 @@
module Ema.Route
( FileRoute (..),
- htmlSlugs,
routeUrl,
- routeFile,
+ decodeUrlRoute,
Slug (unSlug),
decodeSlug,
encodeSlug,
- UrlStrategy (..),
)
where
-import Data.Default (def)
-import Ema.Route.Slug (Slug (unSlug), decodeSlug, encodeSlug)
-import Ema.Route.UrlStrategy
- ( UrlStrategy (..),
- slugFileWithStrategy,
- slugRelUrlWithStrategy,
- )
+import qualified Data.List.NonEmpty as NE
+import qualified Data.Text as T
+import Ema.Route.Slug (Slug (unSlug), decodeSlug, encodeSlug, unicodeNormalize)
+import qualified Network.URI.Encode as UE
+import System.FilePath ((>))
-- | Route to a generated file.
class FileRoute route where
-- | Slug path as well as the extension of the file corresponding to this
-- route.
- encodeRoute :: route -> ([Slug], String)
+ encodeFileRoute :: route -> FilePath
-- | Decode a slug path into a route. The final component of the slug path
-- will contain the extension if there is any.
- decodeRoute :: [Slug] -> Maybe route
-
-htmlSlugs :: [Slug] -> ([Slug], String)
-htmlSlugs = (,".html")
+ decodeFileRoute :: FilePath -> Maybe route
-- | The unit model is useful when using Ema in pure fashion (see @Ema.runEmaPure@) with a single route (index.html) only.
instance FileRoute () where
- encodeRoute () = ([], ".html")
- decodeRoute = \case
- [] -> Just ()
+ encodeFileRoute () = "index.html"
+ decodeFileRoute = \case
+ "index.html" -> Just ()
_ -> Nothing
+-- | Decode a URL path into a route
+decodeUrlRoute :: FileRoute route => Text -> Maybe route
+decodeUrlRoute (toString -> s) =
+ decodeFileRoute s
+ <|> decodeFileRoute (s <> ".html")
+ <|> decodeFileRoute (s > "index.html")
+
-- | Return the relative URL of the given route
--
-- As the returned URL is relative, you will have to either make it absolute (by
-- prepending with `/`) or set the `
Once you fix your code this page will automatically update.