Skip to content

Commit

Permalink
Add tests for R.hs
Browse files Browse the repository at this point in the history
  • Loading branch information
srid committed Jan 13, 2024
1 parent a5e0e19 commit 7e4b272
Show file tree
Hide file tree
Showing 2 changed files with 61 additions and 0 deletions.
1 change: 1 addition & 0 deletions emanote/emanote.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -243,3 +243,4 @@ test-suite test
Emanote.Model.QuerySpec
Emanote.Pandoc.ExternalLinkSpec
Emanote.Pandoc.Renderer.CalloutSpec
Emanote.Route.RSpec
60 changes: 60 additions & 0 deletions emanote/test/Emanote/Route/RSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
module Emanote.Route.RSpec where

import Emanote.Route.Ext
import Emanote.Route.R
import Hedgehog
import Relude
import Test.Hspec
import Test.Hspec.Hedgehog

type SomeExt = ('LMLType 'Md)

spec :: Spec
spec = do
mkRouteFromFilePathSpec
routeInitsSpec

mkRouteFromFilePathSpec :: Spec
mkRouteFromFilePathSpec = describe "mkRouteFromFilePath" $ do
describe "basic" $ do
it "index route" . hedgehog $ do
mkRouteFromFilePath @_ @SomeExt "index.md" === Just indexRoute
it "single slug" . hedgehog $ do
mkRouteFromFilePath "foo.md" === Just r1
it "two slugs" . hedgehog $ do
mkRouteFromFilePath "foo/bar.md" === Just r2
it "three slugs" . hedgehog $ do
mkRouteFromFilePath "foo/bar/qux.md" === Just r3

routeInitsSpec :: Spec
routeInitsSpec = describe "routeInits" $ do
describe "basic" $ do
it "index route returns itself" . hedgehog $ do
routeInits rIndex === one rIndex
it "single slug returns index and itself" . hedgehog $ do
routeInits r1 === rIndex :| [r1]
it "two slugs returns index, first slug, and itself" . hedgehog $ do
routeInits r2 === rIndex :| [r1, r2]
it "three slugs returns index, first slug, second slug, and itself" . hedgehog $ do
routeInits r3 === rIndex :| [r1, r2, r3]

r1 :: R ('LMLType 'Md)
r1 = R $ "foo" :| []

r1Index :: R ('LMLType 'Md)
r1Index = R $ "foo" :| ["index"]

r2 :: R ('LMLType 'Md)
r2 = R $ "foo" :| ["bar"]

r2Index :: R ('LMLType 'Md)
r2Index = R $ "foo" :| ["bar", "index"]

r3 :: R ('LMLType 'Md)
r3 = R $ "foo" :| ["bar", "qux"]

r3Index :: R ('LMLType 'Md)
r3Index = R $ "foo" :| ["bar", "qux", "index"]

rIndex :: R ('LMLType 'Md)
rIndex = R $ "index" :| []

0 comments on commit 7e4b272

Please sign in to comment.