aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Filter.hs
AgeCommit message (Collapse)AuthorFilesLines
2021-12-09Lua: update to latest pandoc-lua-marshal (0.1.1)Albert Krewinkel1-222/+16
- `walk` methods are added to `Block` and `Inline` values; the methods are similar to `pandoc.utils.walk_block` and `pandoc.utils.walk_inline`, but apply to filter also to the element itself, and therefore return a list of element instead of a single element. - Functions of name `Doc` are no longer accepted as alternatives for `Pandoc` filter functions. This functionality was undocumented.
2021-11-27Lua: use package pandoc-lua-marshal (#7719)Albert Krewinkel1-6/+7
The marshaling functions for pandoc's AST are extracted into a separate package. The package comes with a number of changes: - Pandoc's List module was rewritten in C, thereby improving error messages. - Lists of `Block` and `Inline` elements are marshaled using the new list types `Blocks` and `Inlines`, respectively. These types currently behave identical to the generic List type, but give better error messages. This also opens up the possibility of adding element-specific methods to these lists in the future. - Elements of type `MetaValue` are no longer pushed as values which have `.t` and `.tag` properties. This was already true for `MetaString` and `MetaBool` values, which are still marshaled as Lua strings and booleans, respectively. Affected values: + `MetaBlocks` values are marshaled as a `Blocks` list; + `MetaInlines` values are marshaled as a `Inlines` list; + `MetaList` values are marshaled as a generic pandoc `List`s. + `MetaMap` values are marshaled as plain tables and no longer given any metatable. - The test suite for marshaled objects and their constructors has been extended and improved. - A bug in Citation objects, where setting a citation's suffix modified it's prefix, has been fixed.
2021-10-29Lua: use hslua module abstraction where possibleAlbert Krewinkel1-14/+19
This will make it easier to generate module documentation in the future.
2021-10-22Switch to hslua-2.0Albert Krewinkel1-93/+87
The new HsLua version takes a somewhat different approach to marshalling and unmarshalling, relying less on typeclasses and more on specialized types. This allows for better performance and improved error messages. Furthermore, new abstractions allow to document the code and exposed functions.
2021-04-08Lua filter: respect Inlines/Blocks filter functions in pandoc.walk_*Albert Krewinkel1-0/+2
2021-03-15Use foldl' instead of foldl everywhere.John MacFarlane1-1/+2
2021-01-08Update copyright notices for 2021 (#7012)Albert Krewinkel1-2/+2
2020-11-07Lint code in PRs and when committing to master (#6790)Albert Krewinkel1-1/+1
* Remove unused LANGUAGE pragmata * Apply HLint suggestions * Configure HLint to ignore some warnings * Lint code when committing to master
2020-04-17API change: use PandocError for exceptions in Lua subsystemAlbert Krewinkel1-7/+13
The PandocError type is used throughout the Lua subsystem, all Lua functions throw an exception of this type if an error occurs. The `LuaException` type is removed and no longer exported from `Text.Pandoc.Lua`. In its place, a new constructor `PandocLuaError` is added to PandocError.
2020-03-15Use implicit Prelude (#6187)Albert Krewinkel1-2/+0
* Use implicit Prelude The previous behavior was introduced as a fix for #4464. It seems that this change alone did not fix the issue, and `stack ghci` and `cabal repl` only work with GHC 8.4.1 or newer, as no custom Prelude is loaded for these versions. Given this, it seems cleaner to revert to the implicit Prelude. * PandocMonad: remove outdated check for base version Only base versions 4.9 and later are supported, the check for `MIN_VERSION_base(4,8,0)` is therefore unnecessary. * Always use custom prelude Previously, the custom prelude was used only with older GHC versions, as a workaround for problems with ghci. The ghci problems are resolved by replacing package `base` with `base-noprelude`, allowing for consistent use of the custom prelude across all GHC versions.
2020-01-15Lua filters: allow filtering of element lists (#6040)Albert Krewinkel1-29/+68
Lists of Inline and Block elements can now be filtered via `Inlines` and `Blocks` functions, respectively. This is helpful if a filter conversion depends on the order of elements rather than a single element. For example, the following filter can be used to remove all spaces before a citation: function isSpaceBeforeCite (spc, cite) return spc and spc.t == 'Space' and cite and cite.t == 'Cite' end function Inlines (inlines) for i = #inlines-1,1,-1 do if isSpaceBeforeCite(inlines[i], inlines[i+1]) then inlines:remove(i) end end return inlines end Closes: #6038
2019-11-12Switch to new pandoc-types and use Text instead of String [API change].despresc1-2/+2
PR #5884. + Use pandoc-types 1.20 and texmath 0.12. + Text is now used instead of String, with a few exceptions. + In the MediaBag module, some of the types using Strings were switched to use FilePath instead (not Text). + In the Parsing module, new parsers `manyChar`, `many1Char`, `manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`, `mantyUntilChar` have been added: these are like their unsuffixed counterparts but pack some or all of their output. + `glob` in Text.Pandoc.Class still takes String since it seems to be intended as an interface to Glob, which uses strings. It seems to be used only once in the package, in the EPUB writer, so that is not hard to change.
2019-08-16Lua: improve function documentationsAlbert Krewinkel1-1/+4
2019-08-16Lua: traverse nested blocks and inlines in correct orderAlbert Krewinkel1-9/+21
Traversal methods are updated to use the new Walk module such that sequences with nested Inline (or Block) elements are traversed in the order in which they appear in the linearized document. Fixes: #5667
2019-07-02Fix redundant constraint warnings. (#5625)Pete Ryland1-1/+1
2019-03-01Remove license boilerplate.John MacFarlane1-18/+0
The haddock module header contains essentially the same information, so the boilerplate is redundant and just one more thing to get out of sync.
2019-02-16T.P.Lua: split StackInstances into smaller Marshaling modulesAlbert Krewinkel1-1/+1
2019-02-04Add missing copyright notices and remove license boilerplate (#5112)Albert Krewinkel1-4/+4
Quite a few modules were missing copyright notices. This commit adds copyright notices everywhere via haddock module headers. The old license boilerplate comment is redundant with this and has been removed. Update copyright years to 2019. Closes #4592.
2018-10-28T.P.Lua: expose more useful internals (API change)Albert Krewinkel1-0/+20
Newly exported from Text.Pandoc.Lua: - `runFilterFile` to run a Lua filter from file; - data type `Global` and its constructors; and - `setGlobals` to add globals to a Lua environment. This module also contains `Pushable` and `Peekable` instances required to get pandoc's data types to and from Lua. Low-level Lua operation remain hidden in Text.Pandoc.Lua.
2018-10-01Lua filters: report traceback when an error occursAlbert Krewinkel1-5/+4
A proper Lua traceback is added if either loading of a file or execution of a filter function fails. This should be of help to authors of Lua filters who need to debug their code.
2018-09-24Use hslua v1.0.0Albert Krewinkel1-15/+12
2018-09-19Lua filter: cleanup filter execution codeAlbert Krewinkel1-51/+73
2018-03-18Use NoImplicitPrelude and explicitly import Prelude.John MacFarlane1-0/+2
This seems to be necessary if we are to use our custom Prelude with ghci. Closes #4464.
2018-01-12Lua filters: improve error messagesAlbert Krewinkel1-2/+6
Provide more context about the task which caused an error.
2017-12-29data/pandoc.lua: drop function pandoc.global_filterAlbert Krewinkel1-2/+0
The function `global_filter` was used internally to get the implicitly defined global filter. It was of little value to end-users, but caused unnecessary code duplication in pandoc. The function has hence been dropped. Internally, the global filter is now received by interpreting the global table as lua filter. This is a Lua API change.
2017-11-11Functor instance to fix ghc 7.8 warning.John MacFarlane1-1/+1
2017-11-11Add lua filter functions to walk inline and block elements.John MacFarlane1-0/+168
Refactored some code from Text.Pandoc.Lua.PandocModule into new internal module Text.Pandoc.Lua.Filter. Add `walk_inline` and `walk_block` in pandoc lua module.