diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-09-07 11:23:12 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-09-08 22:20:19 -0700 |
commit | 9f984ff26ac248a27212a37ab34754a2e9261e8c (patch) | |
tree | 642ee7fb050587af729fa2585b1c97df510c9d58 /src/Text/Pandoc/Lua | |
parent | 1ccff3339d036db046f37c596bb4ffb6cffbf803 (diff) | |
download | pandoc-9f984ff26ac248a27212a37ab34754a2e9261e8c.tar.gz |
Replace Element and makeHierarchical with makeSections.
Text.Pandoc.Shared:
+ Remove `Element` type [API change]
+ Remove `makeHierarchicalize` [API change]
+ Add `makeSections` [API change]
+ Export `deLink` [API change]
Now that we have Divs, we can use them to represent the structure
of sections, and we don't need a special Element type.
`makeSections` reorganizes a block list, adding Divs with
class `section` around sections, and adding numbering
if needed.
This change also fixes some longstanding issues recognizing
section structure when the document contains Divs.
Closes #3057, see also #997.
All writers have been changed to use `makeSections`.
Note that in the process we have reverted the change
c1d058aeb1c6a331a2cc22786ffaab17f7118ccd
made in response to #5168, which I'm not completely
sure was a good idea.
Lua modules have also been adjusted accordingly.
Existing lua filters that use `hierarchicalize` will
need to be rewritten to use `make_sections`.
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/AST.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Types.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 9 |
3 files changed, 5 insertions, 40 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index 7b428b5f0..c9d61d3e4 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -22,12 +22,9 @@ module Text.Pandoc.Lua.Marshaling.AST import Prelude import Control.Applicative ((<|>)) import Foreign.Lua (Lua, Peekable, Pushable, StackIndex) -import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable - , metatableName) import Text.Pandoc.Definition import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor) import Text.Pandoc.Lua.Marshaling.CommonState () -import Text.Pandoc.Shared (Element (Blk, Sec)) import qualified Foreign.Lua as Lua import qualified Text.Pandoc.Lua.Util as LuaUtil @@ -285,31 +282,3 @@ instance Pushable LuaListAttributes where instance Peekable LuaListAttributes where peek = defineHowTo "get ListAttributes value" . fmap LuaListAttributes . Lua.peek - --- --- Hierarchical elements --- -instance Pushable Element where - push (Blk blk) = Lua.push blk - push sec = pushAnyWithMetatable pushElementMetatable sec - where - pushElementMetatable = ensureUserdataMetatable (metatableName sec) $ - LuaUtil.addFunction "__index" indexElement - -instance Peekable Element where - peek idx = Lua.ltype idx >>= \case - Lua.TypeUserdata -> Lua.peekAny idx - _ -> Blk <$> Lua.peek idx - -indexElement :: Element -> String -> Lua Lua.NumResults -indexElement = \case - (Blk _) -> const (1 <$ Lua.pushnil) -- this shouldn't happen - (Sec lvl num attr label contents) -> fmap (return 1) . \case - "level" -> Lua.push lvl - "numbering" -> Lua.push num - "attr" -> Lua.push (LuaAttr attr) - "label" -> Lua.push label - "contents" -> Lua.push contents - "tag" -> Lua.push "Sec" - "t" -> Lua.push "Sec" - _ -> Lua.pushnil diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs index fdc63cd99..a6bfa529c 100644 --- a/src/Text/Pandoc/Lua/Module/Types.hs +++ b/src/Text/Pandoc/Lua/Module/Types.hs @@ -19,7 +19,6 @@ import Text.Pandoc.Definition import Text.Pandoc.Lua.Marshaling.AST (LuaAttr, LuaListAttributes) import Text.Pandoc.Lua.Marshaling.Version () import Text.Pandoc.Lua.Util (addFunction) -import Text.Pandoc.Shared (Element (..)) import qualified Foreign.Lua as Lua @@ -38,7 +37,6 @@ pushCloneTable = do addFunction "Attr" cloneAttr addFunction "Block" cloneBlock addFunction "Citation" cloneCitation - addFunction "Element" cloneElement addFunction "Inline" cloneInline addFunction "Meta" cloneMeta addFunction "MetaValue" cloneMetaValue @@ -55,9 +53,6 @@ cloneBlock = return cloneCitation :: Citation -> Lua Citation cloneCitation = return -cloneElement :: Element -> Lua Element -cloneElement = return - cloneInline :: Inline -> Lua Inline cloneInline = return diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index 21e3f5674..057e6580b 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -38,7 +38,7 @@ pushModule mbDatadir = do Lua.newtable addFunction "blocks_to_inlines" blocksToInlines addFunction "equals" equals - addFunction "hierarchicalize" hierarchicalize + addFunction "make_sections" makeSections addFunction "normalize_date" normalizeDate addFunction "run_json_filter" (runJSONFilter mbDatadir) addFunction "sha1" sha1 @@ -55,9 +55,10 @@ blocksToInlines blks optSep = do Nothing -> Shared.defaultBlocksSeparator return $ B.toList (Shared.blocksToInlinesWithSep sep blks) --- | Convert list of Pandoc blocks into (hierarchical) list of Elements. -hierarchicalize :: [Block] -> Lua [Shared.Element] -hierarchicalize = return . Shared.hierarchicalize +-- | Convert list of Pandoc blocks into sections using Divs. +makeSections :: Bool -> Lua.Optional Int -> [Block] -> Lua [Block] +makeSections number baselevel = + return . Shared.makeSections number (Lua.fromOptional baselevel) -- | Parse a date and convert (if possible) to "YYYY-MM-DD" format. We -- limit years to the range 1601-9999 (ISO 8601 accepts greater than |