docster/test/Docster/TransformSpec.hs
Your Name 7de2bc811a Add output directory structure and heading-based image naming
- Output files now go to output/<document-name>/ relative to input
- Images named after nearest heading (e.g., file_flow.svg)
- Multiple images under same heading get suffixes: _1, _2, etc.
- Images before any heading use document name as prefix
- Add StateT-based AST traversal for heading tracking
- Add HSpec test suite with 21 tests

🤖 Generated with [Claude Code](https://claude.com/claude-code)

Co-Authored-By: Claude Opus 4.5 <noreply@anthropic.com>
2026-01-05 17:47:49 +00:00

102 lines
3.5 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Docster.TransformSpec (spec) where
import Test.Hspec
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Definition (Inline(..))
import Docster.Types
( OutputDir(..)
, TraversalState(..)
, computeOutputDir
, normalizeHeading
, initialTraversalState
)
import Docster.Transform (inlinesToText)
spec :: Spec
spec = do
describe "normalizeHeading" $ do
it "lowercases and replaces spaces with underscores" $
normalizeHeading "File Flow" `shouldBe` "file_flow"
it "strips non-alphanumeric characters" $
normalizeHeading "API (v2.0)!" `shouldBe` "api_v20"
it "handles multiple spaces" $
normalizeHeading "Hello World" `shouldBe` "hello_world"
it "handles unicode letters" $
normalizeHeading "Diagrama de Flujo" `shouldBe` "diagrama_de_flujo"
it "handles empty string" $
normalizeHeading "" `shouldBe` ""
it "handles heading with only symbols" $
normalizeHeading "!@#$%^" `shouldBe` ""
describe "computeOutputDir" $ do
it "creates output subdir from input path" $
computeOutputDir "docs/readme.md" `shouldBe` OutputDir "docs/output/readme"
it "handles nested paths" $
computeOutputDir "a/b/c/file.md" `shouldBe` OutputDir "a/b/c/output/file"
it "handles current directory (no path)" $
computeOutputDir "readme.md" `shouldBe` OutputDir "output/readme"
it "handles dot prefix path" $
computeOutputDir "./readme.md" `shouldBe` OutputDir "output/readme"
describe "initialTraversalState" $ do
it "starts with no current heading" $
tsCurrentHeading (initialTraversalState "doc") `shouldBe` Nothing
it "starts with empty counters" $
tsHeadingCounters (initialTraversalState "doc") `shouldBe` Map.empty
it "stores document name" $
tsDocumentName (initialTraversalState "myfile") `shouldBe` "myfile"
describe "diagram naming logic" $ do
it "first diagram under heading has no suffix" $
let baseName = "file_flow"
counter = Map.findWithDefault 0 baseName Map.empty
diagName = if counter == 0 then baseName else baseName <> "_" <> T.pack (show counter)
in diagName `shouldBe` "file_flow"
it "second diagram gets _1 suffix" $
let baseName = "file_flow"
counters = Map.singleton "file_flow" 1
counter = Map.findWithDefault 0 baseName counters
diagName = if counter == 0 then baseName else baseName <> "_" <> T.pack (show counter)
in diagName `shouldBe` "file_flow_1"
it "third diagram gets _2 suffix" $
let baseName = "file_flow"
counters = Map.singleton "file_flow" 2
counter = Map.findWithDefault 0 baseName counters
diagName = if counter == 0 then baseName else baseName <> "_" <> T.pack (show counter)
in diagName `shouldBe` "file_flow_2"
it "uses document name when no heading" $
let state = initialTraversalState "readme"
baseName = maybe (tsDocumentName state) id (tsCurrentHeading state)
in baseName `shouldBe` "readme"
describe "inlinesToText" $ do
it "extracts text from Str inline" $
inlinesToText [Str "hello"] `shouldBe` "hello"
it "handles Space" $
inlinesToText [Str "hello", Space, Str "world"] `shouldBe` "hello world"
it "handles nested emphasis" $
inlinesToText [Emph [Str "important"]] `shouldBe` "important"
it "handles Code inline" $
inlinesToText [Code ("", [], []) "code"] `shouldBe` "code"