diff options
| author | Albert Krewinkel <[email protected]> | 2022-09-29 17:24:31 +0200 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2022-09-30 08:33:40 -0700 |
| commit | 5be9052f5fb7283372b3d5497bef499718a34992 (patch) | |
| tree | 80e5805786ef7ab08f363135861e1aa9c8868f6f /pandoc-lua-engine | |
| parent | 79980eee4a1854921d7fb8b14848894b53cc21a7 (diff) | |
[API Change] Extract Lua code into new package pandoc-lua-engine
The flag 'lua53` must now be used with that package if pandoc is to be
compiled against Lua 5.3.
Diffstat (limited to 'pandoc-lua-engine')
65 files changed, 5465 insertions, 0 deletions
diff --git a/pandoc-lua-engine/COPYING.md b/pandoc-lua-engine/COPYING.md new file mode 120000 index 000000000..0c9476f2b --- /dev/null +++ b/pandoc-lua-engine/COPYING.md @@ -0,0 +1 @@ +../COPYING.md
\ No newline at end of file diff --git a/pandoc-lua-engine/README.md b/pandoc-lua-engine/README.md new file mode 100644 index 000000000..81d3a5a1b --- /dev/null +++ b/pandoc-lua-engine/README.md @@ -0,0 +1,6 @@ +# pandoc-lua-engine + +This package provides a Lua pandoc scripting engine based. It +allows to write filters, custom readers, and custom writers in +Lua. + diff --git a/pandoc-lua-engine/pandoc-lua-engine.cabal b/pandoc-lua-engine/pandoc-lua-engine.cabal new file mode 100644 index 000000000..cd8ef14a3 --- /dev/null +++ b/pandoc-lua-engine/pandoc-lua-engine.cabal @@ -0,0 +1,137 @@ +cabal-version: 2.4 +name: pandoc-lua-engine +version: 0.1 +build-type: Simple +license: GPL-2.0-or-later +license-file: COPYING.md +copyright: © 2006-2022 John MacFarlane, 2017-2022 Albert Krewinkel +author: John MacFarlane, Albert Krewinkel +maintainer: Albert Krewinkel <[email protected]> +bug-reports: https://github.com/jgm/pandoc/issues +homepage: https://pandoc.org +category: Text +tested-with: GHC == 8.6.5 + , GHC == 8.8.4 + , GHC == 8.10.7 + , GHC == 9.0.2 + , GHC == 9.2.3 +synopsis: Lua engine to power custom pandoc conversions +description: This package provides a pandoc scripting engine based on + Lua. +extra-source-files: README.md + , test/lua/*.lua + , test/lua/module/*.lua + , test/lua/module/partial.test + , test/lua/module/tiny.epub + , test/sample.lua + , test/tables.custom + , test/tables.native + , test/testsuite.native + , test/writer.custom + +source-repository head + type: git + location: https://github.com/jgm/pandoc.git + subdir: pandoc-lua-engine + +flag lua53 + Description: Embed Lua 5.3 instead of 5.4. + Default: False + +common common-options + default-language: Haskell2010 + build-depends: base >= 4.12 && < 5 + ghc-options: -Wall -fno-warn-unused-do-bind + -Wincomplete-record-updates + -Wnoncanonical-monad-instances + -Wcpp-undef + -Wincomplete-uni-patterns + -Widentities + -Wpartial-fields + -Wmissing-export-lists + -Wmissing-signatures + -fhide-source-paths + + if impl(ghc >= 8.10) + ghc-options: -Wunused-packages + + if impl(ghc >= 9.0) + ghc-options: -Winvalid-haddock + +library + import: common-options + hs-source-dirs: src + exposed-modules: Text.Pandoc.Lua + other-modules: Text.Pandoc.Lua.ErrorConversion + , Text.Pandoc.Lua.Filter + , Text.Pandoc.Lua.Global + , Text.Pandoc.Lua.Init + , Text.Pandoc.Lua.Marshal.CommonState + , Text.Pandoc.Lua.Marshal.Context + , Text.Pandoc.Lua.Marshal.PandocError + , Text.Pandoc.Lua.Marshal.ReaderOptions + , Text.Pandoc.Lua.Marshal.Reference + , Text.Pandoc.Lua.Marshal.Sources + , Text.Pandoc.Lua.Marshal.Template + , Text.Pandoc.Lua.Marshal.WriterOptions + , Text.Pandoc.Lua.Module.MediaBag + , Text.Pandoc.Lua.Module.Pandoc + , Text.Pandoc.Lua.Module.System + , Text.Pandoc.Lua.Module.Template + , Text.Pandoc.Lua.Module.Types + , Text.Pandoc.Lua.Module.Utils + , Text.Pandoc.Lua.Orphans + , Text.Pandoc.Lua.PandocLua + , Text.Pandoc.Lua.Reader + , Text.Pandoc.Lua.Writer + , Text.Pandoc.Lua.Writer.Classic + + build-depends: SHA >= 1.6 && < 1.7 + , bytestring >= 0.9 && < 0.12 + , citeproc >= 0.8 && < 0.9 + , containers >= 0.6.0.1 && < 0.7 + , data-default >= 0.4 && < 0.8 + , doclayout >= 0.4 && < 0.5 + , doctemplates >= 0.10 && < 0.11 + , exceptions >= 0.8 && < 0.11 + , hslua-module-doclayout>= 1.0.4 && < 1.1 + , hslua-module-path >= 1.0.3 && < 1.1 + , hslua-module-system >= 1.0 && < 1.1 + , hslua-module-text >= 1.0 && < 1.1 + , hslua-module-version >= 1.0.3 && < 1.1 + , lpeg >= 1.0.1 && < 1.1 + , mtl >= 2.2 && < 2.3 + , pandoc >= 3.0 && < 3.1 + , pandoc-lua-marshal >= 0.1.7 && < 0.2 + , pandoc-types >= 1.22.2 && < 1.23 + , parsec >= 3.1 && < 3.2 + , text >= 1.1.1 && < 2.1 + if flag(lua53) + build-depends: hslua >= 2.1 && < 2.2, + hslua-aeson >= 2.2.1 && < 2.3 + else + build-depends: hslua >= 2.2.1 && < 2.3 + , hslua-aeson >= 2.2.1 && < 2.3 + +test-suite test-pandoc-lua-engine + import: common-options + type: exitcode-stdio-1.0 + main-is: test-pandoc-lua-engine.hs + hs-source-dirs: test + build-depends: pandoc-lua-engine + , bytestring + , directory + , data-default + , exceptions >= 0.8 && < 0.11 + , filepath + , hslua >= 2.1 && < 2.3 + , pandoc + , pandoc-types >= 1.22.2 && < 1.23 + , tasty + , tasty-golden + , tasty-hunit + , tasty-lua >= 1.0 && < 1.1 + , text >= 1.1.1 && < 2.1 + other-modules: Tests.Lua + , Tests.Lua.Module + , Tests.Lua.Writer diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua.hs new file mode 100644 index 000000000..d6134fc01 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua.hs @@ -0,0 +1,52 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Lua + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Running pandoc Lua filters. +-} +module Text.Pandoc.Lua + ( -- * High-level functions + applyFilter + , readCustom + , writeCustom + -- * Low-level functions + , Global(..) + , setGlobals + , runLua + , runLuaNoEnv + -- * Engine + , getEngine + ) where + +import Control.Monad.IO.Class (MonadIO (liftIO)) +import HsLua.Core (getglobal, openlibs, run, top, tostring) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Filter (applyFilter) +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Init (runLua, runLuaNoEnv) +import Text.Pandoc.Lua.Reader (readCustom) +import Text.Pandoc.Lua.Writer (writeCustom) +import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Scripting (ScriptingEngine (..)) +import qualified Text.Pandoc.UTF8 as UTF8 + +-- | Constructs the Lua scripting engine. +getEngine :: MonadIO m => m ScriptingEngine +getEngine = do + versionName <- liftIO . run @PandocError $ do + openlibs + getglobal "_VERSION" + tostring top + pure $ ScriptingEngine + { engineName = maybe "Lua (unknown version)" UTF8.toText versionName + , engineApplyFilter = applyFilter + , engineReadCustom = readCustom + , engineWriteCustom = writeCustom + } diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs new file mode 100644 index 000000000..3968eba84 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs @@ -0,0 +1,40 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.ErrorConversion + Copyright : © 2020-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Define how Lua errors are converted into @'PandocError'@ Haskell +exceptions, and /vice versa/. +-} +module Text.Pandoc.Lua.ErrorConversion + ( addContextToException + ) where + +import HsLua (LuaError, LuaE, resultToEither, runPeek, top) +import Text.Pandoc.Error (PandocError (PandocLuaError)) +import Text.Pandoc.Lua.Marshal.PandocError (pushPandocError, peekPandocError) + +import qualified Data.Text as T +import qualified HsLua as Lua + +addContextToException :: () +addContextToException = undefined + +-- | Retrieve a @'PandocError'@ from the Lua stack. +popPandocError :: LuaE PandocError PandocError +popPandocError = do + errResult <- runPeek $ peekPandocError top + case resultToEither errResult of + Right x -> return x + Left err -> return $ PandocLuaError (T.pack err) + +-- Ensure conversions between Lua errors and 'PandocError' exceptions +-- are possible. +instance LuaError PandocError where + popException = popPandocError + pushException = pushPandocError + luaException = PandocLuaError . T.pack diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs new file mode 100644 index 000000000..c019095f8 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs @@ -0,0 +1,81 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE IncoherentInstances #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{- | +Module : Text.Pandoc.Lua.Filter +Copyright : © 2012-2022 John MacFarlane, + © 2017-2022 Albert Krewinkel +License : GNU GPL, version 2 or above +Maintainer : Albert Krewinkel <[email protected]> +Stability : alpha + +Types and functions for running Lua filters. +-} +module Text.Pandoc.Lua.Filter + ( applyFilter + ) where +import Control.Monad ((>=>), (<$!>)) +import HsLua as Lua +import Text.Pandoc.Definition +import Text.Pandoc.Filter (Environment (..)) +import Text.Pandoc.Lua.ErrorConversion () +import Text.Pandoc.Lua.Marshal.AST +import Text.Pandoc.Lua.Marshal.Filter +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Init (runLua) +import Control.Exception (throw) +import qualified Data.Text as T +import Text.Pandoc.Class (PandocMonad) +import Control.Monad.Trans (MonadIO) +import Text.Pandoc.Error (PandocError (PandocFilterError, PandocLuaError)) + +-- | Transform document using the filter defined in the given file. +runFilterFile :: FilePath -> Pandoc -> LuaE PandocError Pandoc +runFilterFile filterPath doc = do + oldtop <- gettop + stat <- dofileTrace filterPath + if stat /= Lua.OK + then throwErrorAsException + else do + newtop <- gettop + -- Use the returned filters, or the implicitly defined global + -- filter if nothing was returned. + luaFilters <- forcePeek $ + if newtop - oldtop >= 1 + then peekList peekFilter top + else (:[]) <$!> (liftLua pushglobaltable *> peekFilter top) + settop oldtop + runAll luaFilters doc + +runAll :: [Filter] -> Pandoc -> LuaE PandocError Pandoc +runAll = foldr ((>=>) . applyFully) return + +-- | Run the Lua filter in @filterPath@ for a transformation to the +-- target format (first element in args). Pandoc uses Lua init files to +-- setup the Lua interpreter. +applyFilter :: (PandocMonad m, MonadIO m) + => Environment + -> [String] + -> FilePath + -> Pandoc + -> m Pandoc +applyFilter fenv args fp doc = do + let globals = [ FORMAT $ case args of + x:_ -> T.pack x + _ -> "" + , PANDOC_READER_OPTIONS (envReaderOptions fenv) + , PANDOC_WRITER_OPTIONS (envWriterOptions fenv) + , PANDOC_SCRIPT_FILE fp + ] + runLua >=> forceResult fp $ do + setGlobals globals + runFilterFile fp doc + +forceResult :: (PandocMonad m, MonadIO m) + => FilePath -> Either PandocError Pandoc -> m Pandoc +forceResult fp eitherResult = case eitherResult of + Right x -> return x + Left err -> throw . PandocFilterError (T.pack fp) $ case err of + PandocLuaError msg -> msg + _ -> T.pack $ show err diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs new file mode 100644 index 000000000..702ba7bd5 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs @@ -0,0 +1,74 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Pandoc's Lua globals. +-} +module Text.Pandoc.Lua.Global + ( Global (..) + , setGlobals + ) where + +import HsLua as Lua +import HsLua.Module.Version (pushVersion) +import Text.Pandoc.Class (CommonState) +import Text.Pandoc.Definition (Pandoc, pandocTypesVersion) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Marshal.CommonState (pushCommonState) +import Text.Pandoc.Lua.Marshal.Pandoc (pushPandoc) +import Text.Pandoc.Lua.Marshal.ReaderOptions (pushReaderOptionsReadonly) +import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions) +import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Options (ReaderOptions, WriterOptions) +import Text.Pandoc.Shared (pandocVersion) + +import qualified Data.Text as Text + +-- | Permissible global Lua variables. +data Global = + FORMAT Text.Text + | PANDOC_API_VERSION + | PANDOC_DOCUMENT Pandoc + | PANDOC_READER_OPTIONS ReaderOptions + | PANDOC_WRITER_OPTIONS WriterOptions + | PANDOC_SCRIPT_FILE FilePath + | PANDOC_STATE CommonState + | PANDOC_VERSION + -- Cannot derive instance of Data because of CommonState + +-- | Set all given globals. +setGlobals :: [Global] -> LuaE PandocError () +setGlobals = mapM_ setGlobal + +setGlobal :: Global -> LuaE PandocError () +setGlobal global = case global of + -- This could be simplified if Global was an instance of Data. + FORMAT format -> do + Lua.pushText format + Lua.setglobal "FORMAT" + PANDOC_API_VERSION -> do + pushVersion pandocTypesVersion + Lua.setglobal "PANDOC_API_VERSION" + PANDOC_DOCUMENT doc -> do + pushPandoc doc + Lua.setglobal "PANDOC_DOCUMENT" + PANDOC_READER_OPTIONS ropts -> do + pushReaderOptionsReadonly ropts + Lua.setglobal "PANDOC_READER_OPTIONS" + PANDOC_WRITER_OPTIONS wopts -> do + pushWriterOptions wopts + Lua.setglobal "PANDOC_WRITER_OPTIONS" + PANDOC_SCRIPT_FILE filePath -> do + Lua.pushString filePath + Lua.setglobal "PANDOC_SCRIPT_FILE" + PANDOC_STATE commonState -> do + pushCommonState commonState + Lua.setglobal "PANDOC_STATE" + PANDOC_VERSION -> do + pushVersion pandocVersion + Lua.setglobal "PANDOC_VERSION" diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs new file mode 100644 index 000000000..caa490d52 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs @@ -0,0 +1,167 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Functions to initialize the Lua interpreter. +-} +module Text.Pandoc.Lua.Init + ( runLua + , runLuaNoEnv + ) where + +import Control.Monad (forM, forM_, when) +import Control.Monad.Catch (throwM, try) +import Control.Monad.Trans (MonadIO (..)) +import Data.Maybe (catMaybes) +import HsLua as Lua hiding (status, try) +import Text.Pandoc.Class (PandocMonad, readDataFile) +import Text.Pandoc.Error (PandocError (PandocLuaError)) +import Text.Pandoc.Lua.Marshal.List (newListMetatable, pushListModule) +import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua) +import qualified Data.ByteString.Char8 as Char8 +import qualified Data.Text as T +import qualified Lua.LPeg as LPeg +import qualified HsLua.Aeson +import qualified HsLua.Module.DocLayout as Module.Layout +import qualified HsLua.Module.Path as Module.Path +import qualified HsLua.Module.Text as Module.Text +import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc +import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag +import qualified Text.Pandoc.Lua.Module.System as Pandoc.System +import qualified Text.Pandoc.Lua.Module.Template as Pandoc.Template +import qualified Text.Pandoc.Lua.Module.Types as Pandoc.Types +import qualified Text.Pandoc.Lua.Module.Utils as Pandoc.Utils + +-- | Run the lua interpreter, using pandoc's default way of environment +-- initialization. +runLua :: (PandocMonad m, MonadIO m) + => LuaE PandocError a -> m (Either PandocError a) +runLua action = + runPandocLua . try $ do + initLuaState + liftPandocLua action + +-- | Like 'runLua', but ignores all environment variables like @LUA_PATH@. +runLuaNoEnv :: (PandocMonad m, MonadIO m) + => LuaE PandocError a -> m (Either PandocError a) +runLuaNoEnv action = + runPandocLua . try $ do + liftPandocLua $ do + -- This is undocumented, but works -- the code is adapted from the + -- `lua.c` sources for the default interpreter. + Lua.pushboolean True + Lua.setfield Lua.registryindex "LUA_NOENV" + initLuaState + liftPandocLua action + +-- | Modules that are loaded at startup and assigned to fields in the +-- pandoc module. +-- +-- Note that @pandoc.List@ is not included here for technical reasons; +-- it must be handled separately. +loadedModules :: [Module PandocError] +loadedModules = + [ Pandoc.MediaBag.documentedModule + , Pandoc.System.documentedModule + , Pandoc.Template.documentedModule + , Pandoc.Types.documentedModule + , Pandoc.Utils.documentedModule + , Module.Layout.documentedModule { moduleName = "pandoc.layout" } + , Module.Path.documentedModule { moduleName = "pandoc.path" } + , Module.Text.documentedModule + ] + +-- | Initialize the lua state with all required values +initLuaState :: PandocLua () +initLuaState = do + liftPandocLua Lua.openlibs + initJsonMetatable + initPandocModule + installLpegSearcher + setGlobalModules + loadInitScript "init.lua" + where + initPandocModule :: PandocLua () + initPandocModule = liftPandocLua $ do + -- Push module table + registerModule Module.Pandoc.documentedModule + -- load modules and add them to the `pandoc` module table. + forM_ loadedModules $ \mdl -> do + registerModule mdl + let fieldname (Name mdlname) = Name . + maybe mdlname snd . Char8.uncons . snd $ + Char8.break (== '.') mdlname + Lua.setfield (nth 2) (fieldname $ moduleName mdl) + -- pandoc.List is low-level and must be opened differently. + requirehs "pandoc.List" (const pushListModule) + setfield (nth 2) "List" + -- assign module to global variable + Lua.setglobal "pandoc" + + loadInitScript :: FilePath -> PandocLua () + loadInitScript scriptFile = do + script <- readDataFile scriptFile + status <- liftPandocLua $ Lua.dostring script + when (status /= Lua.OK) . liftPandocLua $ do + err <- popException + let prefix = "Couldn't load '" <> T.pack scriptFile <> "':\n" + throwM . PandocLuaError . (prefix <>) $ case err of + PandocLuaError msg -> msg + _ -> T.pack $ show err + + setGlobalModules :: PandocLua () + setGlobalModules = liftPandocLua $ do + let globalModules = + [ ("lpeg", LPeg.luaopen_lpeg_ptr) -- must be loaded first + , ("re", LPeg.luaopen_re_ptr) -- re depends on lpeg + ] + loadedBuiltInModules <- fmap catMaybes . forM globalModules $ + \(pkgname, luaopen) -> do + Lua.pushcfunction luaopen + usedBuiltIn <- Lua.pcall 0 1 Nothing >>= \case + OK -> do -- all good, loading succeeded + -- register as loaded module so later modules can rely on this + Lua.getfield Lua.registryindex Lua.loaded + Lua.pushvalue (Lua.nth 2) + Lua.setfield (Lua.nth 2) pkgname + Lua.pop 1 -- pop _LOADED + return True + _ -> do -- built-in library failed, load system lib + Lua.pop 1 -- ignore error message + -- Try loading via the normal package loading mechanism. + Lua.getglobal "require" + Lua.pushName pkgname + Lua.call 1 1 -- Throws an exception if loading failed again! + return False + + -- Module on top of stack. Register as global + Lua.setglobal pkgname + return $ if usedBuiltIn then Just pkgname else Nothing + + -- Remove module entry from _LOADED table in registry if we used a + -- built-in library. This ensures that later calls to @require@ will + -- prefer the shared library, if any. + forM_ loadedBuiltInModules $ \pkgname -> do + Lua.getfield Lua.registryindex Lua.loaded + Lua.pushnil + Lua.setfield (Lua.nth 2) pkgname + Lua.pop 1 -- registry + + installLpegSearcher :: PandocLua () + installLpegSearcher = liftPandocLua $ do + Lua.getglobal' "package.searchers" + Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher + Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2) + Lua.pop 1 -- remove 'package.searchers' from stack + +-- | Setup the metatable that's assigned to Lua tables that were created +-- from/via JSON arrays. +initJsonMetatable :: PandocLua () +initJsonMetatable = liftPandocLua $ do + newListMetatable HsLua.Aeson.jsonarray (pure ()) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs new file mode 100644 index 000000000..74ce69887 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs @@ -0,0 +1,68 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Marshal.CommonState + Copyright : © 2012-2022 John MacFarlane + © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Instances to marshal (push) and unmarshal (peek) the common state. +-} +module Text.Pandoc.Lua.Marshal.CommonState + ( typeCommonState + , peekCommonState + , pushCommonState + ) where + +import HsLua +import Text.Pandoc.Class (CommonState (..)) +import Text.Pandoc.Logging (LogMessage, showLogMessage) +import Text.Pandoc.Lua.Marshal.List (pushPandocList) + +-- | Lua type used for the @CommonState@ object. +typeCommonState :: LuaError e => DocumentedType e CommonState +typeCommonState = deftype "pandoc CommonState" [] + [ readonly "input_files" "input files passed to pandoc" + (pushPandocList pushString, stInputFiles) + + , readonly "output_file" "the file to which pandoc will write" + (maybe pushnil pushString, stOutputFile) + + , readonly "log" "list of log messages" + (pushPandocList (pushUD typeLogMessage), stLog) + + , readonly "request_headers" "headers to add for HTTP requests" + (pushPandocList (pushPair pushText pushText), stRequestHeaders) + + , readonly "resource_path" + "path to search for resources like included images" + (pushPandocList pushString, stResourcePath) + + , readonly "source_url" "absolute URL + dir of 1st source file" + (maybe pushnil pushText, stSourceURL) + + , readonly "user_data_dir" "directory to search for data files" + (maybe pushnil pushString, stUserDataDir) + + , readonly "trace" "controls whether tracing messages are issued" + (pushBool, stTrace) + + , readonly "verbosity" "verbosity level" + (pushString . show, stVerbosity) + ] + +peekCommonState :: LuaError e => Peeker e CommonState +peekCommonState = peekUD typeCommonState + +pushCommonState :: LuaError e => Pusher e CommonState +pushCommonState = pushUD typeCommonState + +typeLogMessage :: LuaError e => DocumentedType e LogMessage +typeLogMessage = deftype "pandoc LogMessage" + [ operation Index $ defun "__tostring" + ### liftPure showLogMessage + <#> udparam typeLogMessage "msg" "object" + =#> functionResult pushText "string" "stringified log message" + ] + mempty -- no members diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs new file mode 100644 index 000000000..126f3a82d --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs @@ -0,0 +1,28 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.Context + Copyright : © 2012-2022 John MacFarlane + © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Marshaling instance for doctemplates Context and its components. +-} +module Text.Pandoc.Lua.Marshal.Context () where + +import qualified HsLua as Lua +import HsLua (Pushable) +import Text.DocTemplates (Context(..), Val(..), TemplateTarget) +import Text.DocLayout (render) + +instance (TemplateTarget a, Pushable a) => Pushable (Context a) where + push (Context m) = Lua.push m + +instance (TemplateTarget a, Pushable a) => Pushable (Val a) where + push NullVal = Lua.push () + push (BoolVal b) = Lua.push b + push (MapVal ctx) = Lua.push ctx + push (ListVal xs) = Lua.push xs + push (SimpleVal d) = Lua.push $ render Nothing d diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs new file mode 100644 index 000000000..7f83f2fc0 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs @@ -0,0 +1,50 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Lua.Marshal.PandocError + Copyright : © 2020-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Marshal of @'PandocError'@ values. +-} +module Text.Pandoc.Lua.Marshal.PandocError + ( peekPandocError + , pushPandocError + , typePandocError + ) + where + +import HsLua (LuaError, Peeker, Pusher, liftLua, pushString) +import HsLua.Packaging +import Text.Pandoc.Error (PandocError (PandocLuaError)) + +import qualified HsLua as Lua +import qualified Text.Pandoc.UTF8 as UTF8 + +-- | Lua userdata type definition for PandocError. +typePandocError :: LuaError e => DocumentedType e PandocError +typePandocError = deftype "PandocError" + [ operation Tostring $ defun "__tostring" + ### liftPure (show @PandocError) + <#> udparam typePandocError "obj" "PandocError object" + =#> functionResult pushString "string" "string representation of error." + ] + mempty -- no members + +-- | Peek a @'PandocError'@ element to the Lua stack. +pushPandocError :: LuaError e => Pusher e PandocError +pushPandocError = pushUD typePandocError + +-- | Retrieve a @'PandocError'@ from the Lua stack. +peekPandocError :: LuaError e => Peeker e PandocError +peekPandocError idx = Lua.retrieving "PandocError" $ + liftLua (Lua.ltype idx) >>= \case + Lua.TypeUserdata -> peekUD typePandocError idx + _ -> do + msg <- liftLua $ Lua.state >>= \l -> Lua.liftIO (Lua.popErrorMessage l) + return $ PandocLuaError (UTF8.toText msg) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs new file mode 100644 index 000000000..bec7d81bf --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs @@ -0,0 +1,137 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.ReaderOptions + Copyright : © 2012-2022 John MacFarlane + © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Marshaling instance for ReaderOptions and its components. +-} +module Text.Pandoc.Lua.Marshal.ReaderOptions + ( peekReaderOptions + , pushReaderOptions + , pushReaderOptionsReadonly + ) where + +import Data.Default (def) +import HsLua as Lua +#if !MIN_VERSION_hslua(2,2,0) +import HsLua.Aeson (peekViaJSON, pushViaJSON) +#endif +import Text.Pandoc.Lua.Marshal.List (pushPandocList) +import Text.Pandoc.Options (ReaderOptions (..)) + +-- +-- Reader Options +-- + +-- | Retrieve a ReaderOptions value, either from a normal ReaderOptions +-- value, from a read-only object, or from a table with the same +-- keys as a ReaderOptions object. +peekReaderOptions :: LuaError e => Peeker e ReaderOptions +peekReaderOptions = retrieving "ReaderOptions" . \idx -> + liftLua (ltype idx) >>= \case + TypeUserdata -> choice [ peekUD typeReaderOptions + , peekUD typeReaderOptionsReadonly + ] + idx + TypeTable -> peekReaderOptionsTable idx + _ -> failPeek =<< + typeMismatchMessage "ReaderOptions userdata or table" idx + +-- | Pushes a ReaderOptions value as userdata object. +pushReaderOptions :: LuaError e => Pusher e ReaderOptions +pushReaderOptions = pushUD typeReaderOptions + +-- | Pushes a ReaderOptions object, but makes it read-only. +pushReaderOptionsReadonly :: LuaError e => Pusher e ReaderOptions +pushReaderOptionsReadonly = pushUD typeReaderOptionsReadonly + +-- | ReaderOptions object type for read-only values. +typeReaderOptionsReadonly :: LuaError e => DocumentedType e ReaderOptions +typeReaderOptionsReadonly = deftype "ReaderOptions (read-only)" + [ operation Tostring $ lambda + ### liftPure show + <#> udparam typeReaderOptions "opts" "options to print in native format" + =#> functionResult pushString "string" "Haskell representation" + , operation Newindex $ lambda + ### (failLua "This ReaderOptions value is read-only.") + =?> "Throws an error when called, i.e., an assignment is made." + ] + readerOptionsMembers + +-- | 'ReaderOptions' object type. +typeReaderOptions :: LuaError e => DocumentedType e ReaderOptions +typeReaderOptions = deftype "ReaderOptions" + [ operation Tostring $ lambda + ### liftPure show + <#> udparam typeReaderOptions "opts" "options to print in native format" + =#> functionResult pushString "string" "Haskell representation" + ] + readerOptionsMembers + +-- | Member properties of 'ReaderOptions' Lua values. +readerOptionsMembers :: LuaError e + => [Member e (DocumentedFunction e) ReaderOptions] +readerOptionsMembers = + [ property "abbreviations" "" + (pushSet pushText, readerAbbreviations) + (peekSet peekText, \opts x -> opts{ readerAbbreviations = x }) + , property "columns" "" + (pushIntegral, readerColumns) + (peekIntegral, \opts x -> opts{ readerColumns = x }) + , property "default_image_extension" "" + (pushText, readerDefaultImageExtension) + (peekText, \opts x -> opts{ readerDefaultImageExtension = x }) + , property "extensions" "" + (pushViaJSON, readerExtensions) + (peekViaJSON, \opts x -> opts{ readerExtensions = x }) + , property "indented_code_classes" "" + (pushPandocList pushText, readerIndentedCodeClasses) + (peekList peekText, \opts x -> opts{ readerIndentedCodeClasses = x }) + , property "standalone" "" + (pushBool, readerStandalone) + (peekBool, \opts x -> opts{ readerStandalone = x }) + , property "strip_comments" "" + (pushBool, readerStripComments) + (peekBool, \opts x -> opts{ readerStripComments = x }) + , property "tab_stop" "" + (pushIntegral, readerTabStop) + (peekIntegral, \opts x -> opts{ readerTabStop = x }) + , property "track_changes" "" + (pushViaJSON, readerTrackChanges) + (choice [peekRead, peekViaJSON], \opts x -> opts{ readerTrackChanges = x }) + ] + +-- | Retrieves a 'ReaderOptions' object from a table on the stack, using +-- the default values for all missing fields. +-- +-- Internally, this pushes the default reader options, sets each +-- key/value pair of the table in the userdata value, then retrieves the +-- object again. This will update all fields and complain about unknown +-- keys. +peekReaderOptionsTable :: LuaError e => Peeker e ReaderOptions +peekReaderOptionsTable idx = retrieving "ReaderOptions (table)" $ do + liftLua $ do + absidx <- absindex idx + pushUD typeReaderOptions def + let setFields = do + next absidx >>= \case + False -> return () -- all fields were copied + True -> do + pushvalue (nth 2) *> insert (nth 2) + settable (nth 4) -- set in userdata object + setFields + pushnil -- first key + setFields + peekUD typeReaderOptions top `lastly` pop 1 + +instance Pushable ReaderOptions where + push = pushReaderOptions diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Reference.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Reference.hs new file mode 100644 index 000000000..c23bfef9f --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Reference.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.ReaderOptions + Copyright : © 2012-2022 John MacFarlane + © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Marshal citeproc 'Reference' values. +-} +module Text.Pandoc.Lua.Marshal.Reference + ( pushReference + ) where + +import Citeproc.Types + ( Date (..), DateParts (..), ItemId (..), Name (..), Reference (..) + , Val (..), Variable, fromVariable + ) +import Control.Monad (forM_) +import HsLua hiding (Name, Reference, pushName, peekName) +import Text.Pandoc.Builder (Inlines, toList) +import Text.Pandoc.Lua.Marshal.Inline (pushInlines) +import Text.Pandoc.Lua.Marshal.List (pushPandocList) + +import qualified Data.Map as Map + +-- | Pushes a ReaderOptions value as userdata object. +pushReference :: LuaError e => Pusher e (Reference Inlines) +pushReference reference = do + pushAsTable [ ("id", pushItemId . referenceId) + , ("type", pushText . referenceType) + ] + reference + forM_ (Map.toList $ referenceVariables reference) $ \(var, val) -> do + pushVariable var + pushVal val + rawset (nth 3) + +-- | Pushes an 'ItemId' as a string. +pushItemId :: Pusher e ItemId +pushItemId = pushText . unItemId + +-- | Pushes a person's 'Name' as a table. +pushName :: LuaError e => Pusher e Name +pushName = pushAsTable + [ ("family" , pushTextOrNil . nameFamily) + , ("given" , pushTextOrNil . nameGiven) + , ("dropping-particle" , pushTextOrNil . nameDroppingParticle) + , ("non-dropping-particle" , pushTextOrNil . nameNonDroppingParticle) + , ("suffix" , pushTextOrNil . nameSuffix) + , ("literal" , pushTextOrNil . nameLiteral) + , ("comma-suffix" , pushBoolOrNil . nameCommaSuffix) + , ("static-ordering" , pushBoolOrNil . nameStaticOrdering) + ] + where + pushTextOrNil = \case + Nothing -> pushnil + Just xs -> pushText xs + +-- | Pushes a boolean, but uses @nil@ instead of @false@; table fields +-- are not set unless the value is true. +pushBoolOrNil :: Pusher e Bool +pushBoolOrNil = \case + False -> pushnil + True -> pushBool True + +-- | Pushes a 'Variable' as string. +pushVariable :: Pusher e Variable +pushVariable = pushText . fromVariable + +-- | Pushes a 'Val', i.e., a variable value. +pushVal :: LuaError e => Pusher e (Val Inlines) +pushVal = \case + TextVal t -> pushText t + FancyVal inlns -> pushInlines $ toList inlns + NumVal i -> pushIntegral i + NamesVal names -> pushPandocList pushName names + DateVal date -> pushDate date + _ -> pushText mempty + +-- | Pushes a 'Date' as table. +pushDate :: LuaError e => Pusher e Date +pushDate = pushAsTable + [ ("date-parts", pushPandocList pushDateParts . dateParts) + , ("circa", pushBoolOrNil . dateCirca) + , ("season", maybe pushnil pushIntegral . dateSeason) + , ("literal", maybe pushnil pushText . dateLiteral) + ] + where + -- date parts are lists of Int values + pushDateParts (DateParts dp) = pushPandocList pushIntegral dp diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs new file mode 100644 index 000000000..3b3b58329 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs @@ -0,0 +1,56 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | +Module : Text.Pandoc.Lua.Marshaling.Sources +Copyright : © 2021-2022 Albert Krewinkel +License : GNU GPL, version 2 or above +Maintainer : Albert Krewinkel <[email protected]> + +Marshal 'Sources'. +-} +module Text.Pandoc.Lua.Marshal.Sources + ( peekSources + , pushSources + ) where + +import Control.Monad ((<$!>)) +import Data.Text (Text) +import HsLua as Lua +import Text.Pandoc.Lua.Marshal.List (newListMetatable) +import Text.Pandoc.Sources (Sources (..), toSources) +import Text.Parsec (SourcePos, sourceName) + +-- | Pushes the 'Sources' as a list of lazy Lua objects. +pushSources :: LuaError e => Pusher e Sources +pushSources (Sources srcs) = do + pushList (pushUD typeSource) srcs + newListMetatable "pandoc Sources" $ do + pushName "__tostring" + pushHaskellFunction $ do + sources <- forcePeek $ peekList (peekUD typeSource) (nthBottom 1) + pushText . mconcat $ map snd sources + return 1 + rawset (nth 3) + setmetatable (nth 2) + +-- | Retrieves sources from the stack. +peekSources :: LuaError e => Peeker e Sources +peekSources idx = liftLua (ltype idx) >>= \case + TypeString -> toSources <$!> peekText idx + TypeTable -> Sources <$!> peekList (peekUD typeSource) idx + _ -> Sources . (:[]) <$!> peekUD typeSource idx + +-- | Source object type. +typeSource :: LuaError e => DocumentedType e (SourcePos, Text) +typeSource = deftype "pandoc input source" + [ operation Tostring $ lambda + ### liftPure snd + <#> udparam typeSource "srcs" "Source to print in native format" + =#> functionResult pushText "string" "Haskell representation" + ] + [ readonly "name" "source name" + (pushString, sourceName . fst) + , readonly "text" "source text" + (pushText, snd) + ] diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs new file mode 100644 index 000000000..56878b109 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | +Module : Text.Pandoc.Lua.Marshal.Template +Copyright : © 2021-2022 Albert Krewinkel +License : GNU GPL, version 2 or above +Maintainer : Albert Krewinkel <[email protected]> + +Marshal 'Template' 'Text'. +-} +module Text.Pandoc.Lua.Marshal.Template + ( pushTemplate + , peekTemplate + , typeTemplate + ) where + +import Data.Text (Text) +import HsLua as Lua +import Text.DocTemplates (Template) + +-- | Pushes a 'Template' as a an opaque userdata value. +pushTemplate :: LuaError e => Pusher e (Template Text) +pushTemplate = pushUD typeTemplate + +-- | Retrieves a 'Template' 'Text' value from the stack. +peekTemplate :: LuaError e => Peeker e (Template Text) +peekTemplate = peekUD typeTemplate + +-- | Template object type. +typeTemplate :: LuaError e => DocumentedType e (Template Text) +typeTemplate = deftype "pandoc Template" [] [] diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs new file mode 100644 index 000000000..86df682c5 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs @@ -0,0 +1,244 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.WriterOptions + Copyright : © 2021-2022 Albert Krewinkel, John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Marshaling instance for WriterOptions and its components. +-} +module Text.Pandoc.Lua.Marshal.WriterOptions + ( peekWriterOptions + , pushWriterOptions + ) where + +import Control.Applicative (optional) +import Data.Default (def) +import HsLua as Lua +#if !MIN_VERSION_hslua(2,2,0) +import HsLua.Aeson (peekViaJSON, pushViaJSON) +#endif +import Text.Pandoc.Lua.Marshal.List (pushPandocList) +import Text.Pandoc.Lua.Marshal.Template (peekTemplate, pushTemplate) +import Text.Pandoc.Options (WriterOptions (..)) + +-- +-- Writer Options +-- + +-- | Retrieve a WriterOptions value, either from a normal WriterOptions +-- value, from a read-only object, or from a table with the same +-- keys as a WriterOptions object. +peekWriterOptions :: LuaError e => Peeker e WriterOptions +peekWriterOptions = retrieving "WriterOptions" . \idx -> + liftLua (ltype idx) >>= \case + TypeUserdata -> peekUD typeWriterOptions idx + TypeTable -> peekWriterOptionsTable idx + _ -> failPeek =<< + typeMismatchMessage "WriterOptions userdata or table" idx + +-- | Pushes a WriterOptions value as userdata object. +pushWriterOptions :: LuaError e => Pusher e WriterOptions +pushWriterOptions = pushUD typeWriterOptions + +-- | 'WriterOptions' object type. +typeWriterOptions :: LuaError e => DocumentedType e WriterOptions +typeWriterOptions = deftype "WriterOptions" + [ operation Tostring $ lambda + ### liftPure show + <#> udparam typeWriterOptions "opts" "options to print in native format" + =#> functionResult pushString "string" "Haskell representation" + ] + [ property "cite_method" + "How to print cites" + (pushViaJSON, writerCiteMethod) + (peekViaJSON, \opts x -> opts{ writerCiteMethod = x }) + + , property "columns" + "Characters in a line (for text wrapping)" + (pushIntegral, writerColumns) + (peekIntegral, \opts x -> opts{ writerColumns = x }) + + , property "dpi" + "DPI for pixel to/from inch/cm conversions" + (pushIntegral, writerDpi) + (peekIntegral, \opts x -> opts{ writerDpi = x }) + + , property "email_obfuscation" + "How to obfuscate emails" + (pushViaJSON, writerEmailObfuscation) + (peekViaJSON, \opts x -> opts{ writerEmailObfuscation = x }) + + , property "epub_chapter_level" + "Header level for chapters (separate files)" + (pushIntegral, writerEpubChapterLevel) + (peekIntegral, \opts x -> opts{ writerEpubChapterLevel = x }) + + , property "epub_fonts" + "Paths to fonts to embed" + (pushPandocList pushString, writerEpubFonts) + (peekList peekString, \opts x -> opts{ writerEpubFonts = x }) + + , property "epub_metadata" + "Metadata to include in EPUB" + (maybe pushnil pushText, writerEpubMetadata) + (optional . peekText, \opts x -> opts{ writerEpubMetadata = x }) + + , property "epub_subdirectory" + "Subdir for epub in OCF" + (pushText, writerEpubSubdirectory) + (peekText, \opts x -> opts{ writerEpubSubdirectory = x }) + + , property "extensions" + "Markdown extensions that can be used" + (pushViaJSON, writerExtensions) + (peekViaJSON, \opts x -> opts{ writerExtensions = x }) + + , property "highlight_style" + "Style to use for highlighting (nil = no highlighting)" + (maybe pushnil pushViaJSON, writerHighlightStyle) + (optional . peekViaJSON, \opts x -> opts{ writerHighlightStyle = x }) + + , property "html_math_method" + "How to print math in HTML" + (pushViaJSON, writerHTMLMathMethod) + (peekViaJSON, \opts x -> opts{ writerHTMLMathMethod = x }) + + , property "html_q_tags" + "Use @<q>@ tags for quotes in HTML" + (pushBool, writerHtmlQTags) + (peekBool, \opts x -> opts{ writerHtmlQTags = x }) + + , property "identifier_prefix" + "Prefix for section & note ids in HTML and for footnote marks in markdown" + (pushText, writerIdentifierPrefix) + (peekText, \opts x -> opts{ writerIdentifierPrefix = x }) + + , property "incremental" + "True if lists should be incremental" + (pushBool, writerIncremental) + (peekBool, \opts x -> opts{ writerIncremental = x }) + + , property "listings" + "Use listings package for code" + (pushBool, writerListings) + (peekBool, \opts x -> opts{ writerListings = x }) + + , property "number_offset" + "Starting number for section, subsection, ..." + (pushPandocList pushIntegral, writerNumberOffset) + (peekList peekIntegral, \opts x -> opts{ writerNumberOffset = x }) + + , property "number_sections" + "Number sections in LaTeX" + (pushBool, writerNumberSections) + (peekBool, \opts x -> opts{ writerNumberSections = x }) + + , property "prefer_ascii" + "Prefer ASCII representations of characters when possible" + (pushBool, writerPreferAscii) + (peekBool, \opts x -> opts{ writerPreferAscii = x }) + + , property "reference_doc" + "Path to reference document if specified" + (maybe pushnil pushString, writerReferenceDoc) + (optional . peekString, \opts x -> opts{ writerReferenceDoc = x }) + + , property "reference_links" + "Use reference links in writing markdown, rst" + (pushBool, writerReferenceLinks) + (peekBool, \opts x -> opts{ writerReferenceLinks = x }) + + , property "reference_location" + "Location of footnotes and references for writing markdown" + (pushViaJSON, writerReferenceLocation) + (peekViaJSON, \opts x -> opts{ writerReferenceLocation = x }) + + , property "section_divs" + "Put sections in div tags in HTML" + (pushBool, writerSectionDivs) + (peekBool, \opts x -> opts{ writerSectionDivs = x }) + + , property "setext_headers" + "Use setext headers for levels 1-2 in markdown" + (pushBool, writerSetextHeaders) + (peekBool, \opts x -> opts{ writerSetextHeaders = x }) + + , property "slide_level" + "Force header level of slides" + (maybe pushnil pushIntegral, writerSlideLevel) + (optional . peekIntegral, \opts x -> opts{ writerSlideLevel = x }) + + -- , property "syntax_map" "Syntax highlighting definition" + -- (pushViaJSON, writerSyntaxMap) + -- (peekViaJSON, \opts x -> opts{ writerSyntaxMap = x }) + -- :: SyntaxMap + + , property "tab_stop" + "Tabstop for conversion btw spaces and tabs" + (pushIntegral, writerTabStop) + (peekIntegral, \opts x -> opts{ writerTabStop = x }) + + , property "table_of_contents" + "Include table of contents" + (pushBool, writerTableOfContents) + (peekBool, \opts x -> opts{ writerTableOfContents = x }) + + , property "template" + "Template to use" + (maybe pushnil pushTemplate, writerTemplate) + (optional . peekTemplate, \opts x -> opts{ writerTemplate = x }) + -- :: Maybe (Template Text) + + , property "toc_depth" + "Number of levels to include in TOC" + (pushIntegral, writerTOCDepth) + (peekIntegral, \opts x -> opts{ writerTOCDepth = x }) + + , property "top_level_division" + "Type of top-level divisions" + (pushViaJSON, writerTopLevelDivision) + (peekViaJSON, \opts x -> opts{ writerTopLevelDivision = x }) + + , property "variables" + "Variables to set in template" + (pushViaJSON, writerVariables) + (peekViaJSON, \opts x -> opts{ writerVariables = x }) + + , property "wrap_text" + "Option for wrapping text" + (pushViaJSON, writerWrapText) + (peekViaJSON, \opts x -> opts{ writerWrapText = x }) + ] + +-- | Retrieves a 'WriterOptions' object from a table on the stack, using +-- the default values for all missing fields. +-- +-- Internally, this pushes the default writer options, sets each +-- key/value pair of the table in the userdata value, then retrieves the +-- object again. This will update all fields and complain about unknown +-- keys. +peekWriterOptionsTable :: LuaError e => Peeker e WriterOptions +peekWriterOptionsTable idx = retrieving "WriterOptions (table)" $ do + liftLua $ do + absidx <- absindex idx + pushUD typeWriterOptions def + let setFields = do + next absidx >>= \case + False -> return () -- all fields were copied + True -> do + pushvalue (nth 2) *> insert (nth 2) + settable (nth 4) -- set in userdata object + setFields + pushnil -- first key + setFields + peekUD typeWriterOptions top `lastly` pop 1 + +instance Pushable WriterOptions where + push = pushWriterOptions diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs new file mode 100644 index 000000000..ca028f444 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs @@ -0,0 +1,142 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Module.MediaBag + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + Maintainer : Albert Krewinkel <[email protected]> + +The Lua module @pandoc.mediabag@. +-} +module Text.Pandoc.Lua.Module.MediaBag + ( documentedModule + ) where + +import Prelude hiding (lookup) +import Data.Maybe (fromMaybe) +import HsLua ( LuaE, DocumentedFunction, Module (..) + , (<#>), (###), (=#>), (=?>), (#?), defun, functionResult + , opt, parameter, stringParam, textParam) +import Text.Pandoc.Class ( CommonState (..), fetchItem, fillMediaBag + , getMediaBag, modifyCommonState, setMediaBag) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc, pushPandoc) +import Text.Pandoc.Lua.Marshal.List (pushPandocList) +import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Lua.PandocLua (unPandocLua) +import Text.Pandoc.MIME (MimeType) + +import qualified Data.ByteString.Lazy as BL +import qualified HsLua as Lua +import qualified Text.Pandoc.MediaBag as MB + +-- +-- MediaBag submodule +-- +documentedModule :: Module PandocError +documentedModule = Module + { moduleName = "pandoc.mediabag" + , moduleDescription = "mediabag access" + , moduleFields = [] + , moduleFunctions = + [ delete + , empty + , fetch + , fill + , insert + , items + , list + , lookup + ] + , moduleOperations = [] + } + +-- | Delete a single item from the media bag. +delete :: DocumentedFunction PandocError +delete = defun "delete" + ### (\fp -> unPandocLua $ modifyCommonState + (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) })) + <#> stringParam "filepath" "filename of item to delete" + =#> [] + + +-- | Delete all items from the media bag. +empty :: DocumentedFunction PandocError +empty = defun "empty" + ### unPandocLua (modifyCommonState (\st -> st { stMediaBag = mempty })) + =#> [] + +-- | Fill the mediabag with all images in the document that aren't +-- present yet. +fill :: DocumentedFunction PandocError +fill = defun "fill" + ### unPandocLua . fillMediaBag + <#> parameter peekPandoc "Pandoc" "doc" + "document from which to fill the mediabag" + =#> functionResult pushPandoc "Pandoc" "modified document" + #? ("Fills the mediabag with the images in the given document.\n" <> + "An image that cannot be retrieved will be replaced with a Span\n" <> + "of class \"image\" that contains the image description.\n" <> + "" <> + "Images for which the mediabag already contains an item will\n" <> + "not be processed again.") + +-- | Insert a new item into the media bag. +insert :: DocumentedFunction PandocError +insert = defun "insert" + ### (\fp mmime contents -> unPandocLua $ do + mb <- getMediaBag + setMediaBag $ MB.insertMedia fp mmime contents mb + return (Lua.NumResults 0)) + <#> stringParam "filepath" "item file path" + <#> opt (textParam "mimetype" "the item's MIME type") + <#> parameter Lua.peekLazyByteString "string" "contents" "binary contents" + =#> [] + +-- | Returns iterator values to be used with a Lua @for@ loop. +items :: DocumentedFunction PandocError +items = defun "items" + ### (do + mb <-unPandocLua getMediaBag + let pushItem (fp, mimetype, contents) = do + Lua.pushString fp + Lua.pushText mimetype + Lua.pushByteString $ BL.toStrict contents + return (Lua.NumResults 3) + Lua.pushIterator pushItem (MB.mediaItems mb)) + =?> "Iterator triple" + +-- | Function to lookup a value in the mediabag. +lookup :: DocumentedFunction PandocError +lookup = defun "lookup" + ### (\fp -> unPandocLua (MB.lookupMedia fp <$> getMediaBag) >>= \case + Nothing -> 1 <$ Lua.pushnil + Just item -> 2 <$ do + Lua.pushText $ MB.mediaMimeType item + Lua.pushLazyByteString $ MB.mediaContents item) + <#> stringParam "filepath" "path of item to lookup" + =?> "MIME type and contents" + +-- | Function listing all mediabag items. +list :: DocumentedFunction PandocError +list = defun "list" + ### (unPandocLua (MB.mediaDirectory <$> getMediaBag)) + =#> functionResult (pushPandocList pushEntry) "table" "list of entry triples" + where + pushEntry :: (FilePath, MimeType, Int) -> LuaE PandocError () + pushEntry (fp, mimeType, contentLength) = do + Lua.newtable + Lua.pushName "path" *> Lua.pushString fp *> Lua.rawset (-3) + Lua.pushName "type" *> Lua.pushText mimeType *> Lua.rawset (-3) + Lua.pushName "length" *> Lua.pushIntegral contentLength *> Lua.rawset (-3) + +-- | Lua function to retrieve a new item. +fetch :: DocumentedFunction PandocError +fetch = defun "fetch" + ### (\src -> do + (bs, mimeType) <- unPandocLua $ fetchItem src + Lua.pushText $ fromMaybe "" mimeType + Lua.pushByteString bs + return 2) + <#> textParam "src" "URI to fetch" + =?> "Returns two string values: the fetched contents and the mimetype." diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs new file mode 100644 index 000000000..e708f4345 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -0,0 +1,320 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Lua.Module.Pandoc + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Pandoc module for lua. +-} +module Text.Pandoc.Lua.Module.Pandoc + ( pushModule + , documentedModule + ) where + +import Prelude hiding (read) +import Control.Applicative ((<|>)) +import Control.Monad (forM_, when) +import Control.Monad.Catch (catch, throwM) +import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr) +import Data.Default (Default (..)) +import Data.Maybe (fromMaybe) +import Data.Proxy (Proxy (Proxy)) +import HsLua hiding (pushModule) +import System.Exit (ExitCode (..)) +import Text.Pandoc.Definition +import Text.Pandoc.Error (PandocError (..)) +import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Lua.Marshal.AST +import Text.Pandoc.Lua.Marshal.Filter (peekFilter) +import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions + , pushReaderOptions) +import Text.Pandoc.Lua.Marshal.Sources (peekSources) +import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions + , pushWriterOptions) +import Text.Pandoc.Lua.Module.Utils (sha1) +import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua), liftPandocLua) +import Text.Pandoc.Options ( ReaderOptions (readerExtensions) + , WriterOptions (writerExtensions) ) +import Text.Pandoc.Process (pipeProcess) +import Text.Pandoc.Readers (Reader (..), getReader, readers) +import Text.Pandoc.Sources (toSources) +import Text.Pandoc.Writers (Writer (..), getWriter, writers) + +import qualified HsLua as Lua +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Lazy.Char8 as BSL +import qualified Data.Set as Set +import qualified Data.Text as T +import qualified Text.Pandoc.UTF8 as UTF8 + +-- | Push the "pandoc" package to the Lua stack. Requires the `List` +-- module to be loadable. +pushModule :: PandocLua NumResults +pushModule = do + liftPandocLua $ Lua.pushModule documentedModule + return 1 + +documentedModule :: Module PandocError +documentedModule = Module + { moduleName = "pandoc" + , moduleDescription = T.unlines + [ "Lua functions for pandoc scripts; includes constructors for" + , "document elements, functions to parse text in a given" + , "format, and functions to filter and modify a subtree." + ] + , moduleFields = readersField : writersField : + stringConstants ++ [inlineField, blockField] + , moduleOperations = [] + , moduleFunctions = mconcat + [ functions + , otherConstructors + , blockConstructors + , inlineConstructors + , metaValueConstructors + ] + } + +-- | Set of input formats accepted by @read@. +readersField :: Field PandocError +readersField = Field + { fieldName = "readers" + , fieldDescription = T.unlines + [ "Set of formats that pandoc can parse. All keys in this table can" + , "be used as the `format` value in `pandoc.read`." + ] + , fieldPushValue = pushSet pushText $ + Set.fromList (map fst (readers @PandocLua)) + } + +-- | Set of input formats accepted by @write@. +writersField :: Field PandocError +writersField = Field + { fieldName = "writers" + , fieldDescription = T.unlines + [ "Set of formats that pandoc can generate. All keys in this table" + , "can be used as the `format` value in `pandoc.write`." + ] + , fieldPushValue = pushSet pushText $ + Set.fromList (map fst (writers @PandocLua)) + } + +-- | Inline table field +inlineField :: Field PandocError +inlineField = Field + { fieldName = "Inline" + , fieldDescription = "Inline constructors, nested under 'constructors'." + -- the nesting happens for historical reasons and should probably be + -- changed. + , fieldPushValue = pushWithConstructorsSubtable inlineConstructors + } + +-- | @Block@ module field +blockField :: Field PandocError +blockField = Field + { fieldName = "Block" + , fieldDescription = "Inline constructors, nested under 'constructors'." + -- the nesting happens for historical reasons and should probably be + -- changed. + , fieldPushValue = pushWithConstructorsSubtable blockConstructors + } + +pushWithConstructorsSubtable :: [DocumentedFunction PandocError] + -> LuaE PandocError () +pushWithConstructorsSubtable constructors = do + newtable -- Field table + newtable -- constructor table + pushName "constructor" *> pushvalue (nth 2) *> rawset (nth 4) + forM_ constructors $ \fn -> do + pushName (functionName fn) + pushDocumentedFunction fn + rawset (nth 3) + pop 1 -- pop constructor table + +otherConstructors :: LuaError e => [DocumentedFunction e] +otherConstructors = + [ mkPandoc + , mkMeta + , mkAttr + , mkAttributeList + , mkBlocks + , mkCitation + , mkCell + , mkRow + , mkTableHead + , mkTableFoot + , mkInlines + , mkListAttributes + , mkSimpleTable + + , defun "ReaderOptions" + ### liftPure id + <#> parameter peekReaderOptions "ReaderOptions|table" "opts" "reader options" + =#> functionResult pushReaderOptions "ReaderOptions" "new object" + #? "Creates a new ReaderOptions value." + + , defun "WriterOptions" + ### liftPure id + <#> parameter peekWriterOptions "WriterOptions|table" "opts" + "writer options" + =#> functionResult pushWriterOptions "WriterOptions" "new object" + #? "Creates a new WriterOptions value." + ] + +stringConstants :: [Field e] +stringConstants = + let constrs :: forall a. Data a => Proxy a -> [String] + constrs _ = map showConstr . dataTypeConstrs . dataTypeOf @a $ undefined + nullaryConstructors = mconcat + [ constrs (Proxy @ListNumberStyle) + , constrs (Proxy @ListNumberDelim) + , constrs (Proxy @QuoteType) + , constrs (Proxy @MathType) + , constrs (Proxy @Alignment) + , constrs (Proxy @CitationMode) + ] + toField s = Field + { fieldName = T.pack s + , fieldDescription = T.pack s + , fieldPushValue = pushString s + } + in map toField nullaryConstructors + +functions :: [DocumentedFunction PandocError] +functions = + [ defun "pipe" + ### (\command args input -> do + (ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input + `catch` (throwM . PandocIOError "pipe") + case ec of + ExitSuccess -> 1 <$ Lua.pushLazyByteString output + ExitFailure n -> do + pushPipeError (PipeError (T.pack command) n output) + Lua.error) + <#> parameter peekString "string" "command" "path to executable" + <#> parameter (peekList peekString) "{string,...}" "args" + "list of arguments" + <#> parameter peekLazyByteString "string" "input" + "input passed to process via stdin" + =?> "output string, or error triple" + + , defun "read" + ### (\content mformatspec mreaderOptions -> do + let formatSpec = fromMaybe "markdown" mformatspec + readerOpts = fromMaybe def mreaderOptions + readAction = getReader formatSpec >>= \case + (TextReader r, es) -> + r readerOpts{readerExtensions = es} + (case content of + Left bs -> toSources $ UTF8.toText bs + Right sources -> sources) + (ByteStringReader r, es) -> + case content of + Left bs -> r readerOpts{readerExtensions = es} + (BSL.fromStrict bs) + Right _ -> liftPandocLua $ Lua.failLua + "Cannot use bytestring reader with Sources" + try (unPandocLua readAction) >>= \case + Right pd -> + -- success, got a Pandoc document + return pd + Left (PandocUnknownReaderError f) -> + Lua.failLua . T.unpack $ "Unknown reader: " <> f + Left (PandocUnsupportedExtensionError e f) -> + Lua.failLua . T.unpack $ + "Extension " <> e <> " not supported for " <> f + Left e -> + throwM e) + <#> parameter (\idx -> (Left <$> peekByteString idx) + <|> (Right <$> peekSources idx)) + "string|Sources" "content" "text to parse" + <#> opt (textParam "formatspec" "format and extensions") + <#> opt (parameter peekReaderOptions "ReaderOptions" "reader_options" + "reader options") + =#> functionResult pushPandoc "Pandoc" "result document" + + , sha1 + + , defun "walk_block" + ### walkElement + <#> parameter peekBlockFuzzy "Block" "block" "element to traverse" + <#> parameter peekFilter "Filter" "lua_filter" "filter functions" + =#> functionResult pushBlock "Block" "modified Block" + + , defun "walk_inline" + ### walkElement + <#> parameter peekInlineFuzzy "Inline" "inline" "element to traverse" + <#> parameter peekFilter "Filter" "lua_filter" "filter functions" + =#> functionResult pushInline "Inline" "modified Inline" + + , defun "write" + ### (\doc mformatspec mwriterOpts -> do + let formatSpec = fromMaybe "html" mformatspec + writerOpts = fromMaybe def mwriterOpts + unPandocLua $ getWriter formatSpec >>= \case + (TextWriter w, es) -> Right <$> + w writerOpts{ writerExtensions = es } doc + (ByteStringWriter w, es) -> Left <$> + w writerOpts{ writerExtensions = es } doc) + <#> parameter peekPandoc "Pandoc" "doc" "document to convert" + <#> opt (textParam "formatspec" "format and extensions") + <#> opt (parameter peekWriterOptions "WriterOptions" "writer_options" + "writer options") + =#> functionResult (either pushLazyByteString pushText) "string" + "result document" + ] + where + walkElement x f = + walkInlineSplicing f x + >>= walkInlinesStraight f + >>= walkBlockSplicing f + >>= walkBlocksStraight f + +data PipeError = PipeError + { pipeErrorCommand :: T.Text + , pipeErrorCode :: Int + , pipeErrorOutput :: BL.ByteString + } + +peekPipeError :: LuaError e => StackIndex -> LuaE e PipeError +peekPipeError idx = + PipeError + <$> (Lua.getfield idx "command" *> Lua.peek (-1) <* Lua.pop 1) + <*> (Lua.getfield idx "error_code" *> Lua.peek (-1) <* Lua.pop 1) + <*> (Lua.getfield idx "output" *> Lua.peek (-1) <* Lua.pop 1) + +pushPipeError :: LuaError e => Pusher e PipeError +pushPipeError pipeErr = do + pushAsTable [ ("command" , pushText . pipeErrorCommand) + , ("error_code" , pushIntegral . pipeErrorCode) + , ("output" , pushLazyByteString . pipeErrorOutput) + ] pipeErr + pushPipeErrorMetaTable + Lua.setmetatable (nth 2) + where + pushPipeErrorMetaTable :: LuaError e => LuaE e () + pushPipeErrorMetaTable = do + v <- Lua.newmetatable "pandoc pipe error" + when v $ do + pushName "__tostring" + pushHaskellFunction pipeErrorMessage + rawset (nth 3) + + pipeErrorMessage :: LuaError e => LuaE e NumResults + pipeErrorMessage = do + (PipeError cmd errorCode output) <- peekPipeError (nthBottom 1) + pushByteString . BSL.toStrict . BSL.concat $ + [ BSL.pack "Error running " + , BSL.pack $ T.unpack cmd + , BSL.pack " (error code " + , BSL.pack $ show errorCode + , BSL.pack "): " + , if output == mempty then BSL.pack "<no output>" else output + ] + return (NumResults 1) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs new file mode 100644 index 000000000..70ef1b315 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{- | + Module : Text.Pandoc.Lua.Module.System + Copyright : © 2019-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Pandoc's system Lua module. +-} +module Text.Pandoc.Lua.Module.System + ( documentedModule + ) where + +import HsLua +import HsLua.Module.System + (arch, env, getwd, ls, mkdir, os, rmdir, with_env, with_tmpdir, with_wd) + +-- | Push the pandoc.system module on the Lua stack. +documentedModule :: LuaError e => Module e +documentedModule = Module + { moduleName = "pandoc.system" + , moduleDescription = "system functions" + , moduleFields = + [ arch + , os + ] + , moduleFunctions = + [ setName "environment" env + , setName "get_working_directory" getwd + , setName "list_directory" ls + , setName "make_directory" mkdir + , setName "remove_directory" rmdir + , setName "with_environment" with_env + , setName "with_temporary_directory" with_tmpdir + , setName "with_working_directory" with_wd + ] + , moduleOperations = [] + } diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs new file mode 100644 index 000000000..967fe31a8 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs @@ -0,0 +1,61 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Module.Template + Copyright : Copyright © 2022 Albert Krewinkel, John MacFarlane + License : GNU GPL, version 2 or above + Maintainer : Albert Krewinkel <[email protected]> + +Lua module to handle pandoc templates. +-} +module Text.Pandoc.Lua.Module.Template + ( documentedModule + ) where + +import HsLua +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Marshal.Template (pushTemplate) +import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua), liftPandocLua) +import Text.Pandoc.Templates + (compileTemplate, getDefaultTemplate, runWithPartials, runWithDefaultPartials) + +import qualified Data.Text as T + +-- | The "pandoc.template" module. +documentedModule :: Module PandocError +documentedModule = Module + { moduleName = "pandoc.template" + , moduleDescription = T.unlines + [ "Lua functions for pandoc templates." + ] + , moduleFields = [] + , moduleOperations = [] + , moduleFunctions = functions + } + +-- | Template module functions. +functions :: [DocumentedFunction PandocError] +functions = + [ defun "compile" + ### (\template mfilepath -> unPandocLua $ + case mfilepath of + Just fp -> runWithPartials (compileTemplate fp template) + Nothing -> runWithDefaultPartials + (compileTemplate "templates/default" template)) + <#> parameter peekText "string" "template" "template string" + <#> opt (stringParam "templ_path" "template path") + =#> functionResult (either failLua pushTemplate) "pandoc Template" + "compiled template" + + , defun "default" + ### (\mformat -> unPandocLua $ do + let getFORMAT = liftPandocLua $ do + getglobal "FORMAT" + forcePeek $ peekText top `lastly` pop 1 + format <- maybe getFORMAT pure mformat + getDefaultTemplate format) + <#> opt (textParam "writer" + "writer for which the template should be returned.") + =#> functionResult pushText "string" + "string representation of the writer's default template" + + ] diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs new file mode 100644 index 000000000..b8d45d93e --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs @@ -0,0 +1,42 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Module.Types + Copyright : © 2019-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Pandoc data type constructors. +-} +module Text.Pandoc.Lua.Module.Types + ( documentedModule + ) where + +import HsLua ( Module (..), (###), (<#>), (=#>) + , defun, functionResult, parameter) +import HsLua.Module.Version (peekVersionFuzzy, pushVersion) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.ErrorConversion () + +-- | Push the pandoc.types module on the Lua stack. +documentedModule :: Module PandocError +documentedModule = Module + { moduleName = "pandoc.types" + , moduleDescription = + "Constructors for types that are not part of the pandoc AST." + , moduleFields = [] + , moduleFunctions = + [ defun "Version" + ### return + <#> parameter peekVersionFuzzy "string|integer|{integer,...}|Version" + "version_specifier" + (mconcat [ "either a version string like `'2.7.3'`, " + , "a single integer like `2`, " + , "list of integers like `{2,7,3}`, " + , "or a Version object" + ]) + =#> functionResult pushVersion "Version" "A new Version object." + ] + , moduleOperations = [] + } diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs new file mode 100644 index 000000000..33349870c --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs @@ -0,0 +1,239 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Lua.Module.Utils + Copyright : Copyright © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Utility module for Lua, exposing internal helper functions. +-} +module Text.Pandoc.Lua.Module.Utils + ( documentedModule + , sha1 + ) where + +import Control.Applicative ((<|>)) +import Control.Monad ((<$!>)) +import Data.Data (showConstr, toConstr) +import Data.Default (def) +import Data.Maybe (fromMaybe) +import Data.Version (Version) +import HsLua as Lua +import HsLua.Module.Version (peekVersionFuzzy, pushVersion) +import Text.Pandoc.Citeproc (getReferences, processCitations) +import Text.Pandoc.Definition +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Filter (applyJSONFilter) +import Text.Pandoc.Lua.Marshal.AST +import Text.Pandoc.Lua.Marshal.Reference +import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua)) + +import qualified Data.Digest.Pure.SHA as SHA +import qualified Data.ByteString.Lazy as BSL +import qualified Data.Map as Map +import qualified Data.Text as T +import qualified Text.Pandoc.Builder as B +import qualified Text.Pandoc.Shared as Shared +import qualified Text.Pandoc.UTF8 as UTF8 +import qualified Text.Pandoc.Writers.Shared as Shared + +-- | Push the "pandoc.utils" module to the Lua stack. +documentedModule :: Module PandocError +documentedModule = Module + { moduleName = "pandoc.utils" + , moduleDescription = "pandoc utility functions" + , moduleFields = [] + , moduleOperations = [] + , moduleFunctions = + [ defun "blocks_to_inlines" + ### (\blks mSep -> do + let sep = maybe Shared.defaultBlocksSeparator B.fromList mSep + return $ B.toList (Shared.blocksToInlinesWithSep sep blks)) + <#> parameter (peekList peekBlock) "list of blocks" + "blocks" "" + <#> opt (parameter (peekList peekInline) "list of inlines" "inline" "") + =#> functionResult pushInlines "list of inlines" "" + + , defun "citeproc" + ### unPandocLua . processCitations + <#> parameter peekPandoc "Pandoc" "doc" "document" + =#> functionResult pushPandoc "Pandoc" "processed document" + #? T.unwords + [ "Process the citations in the file, replacing them with " + , "rendered citations and adding a bibliography. " + , "See the manual section on citation rendering for details." + ] + + , defun "equals" + ### equal + <#> parameter pure "AST element" "elem1" "" + <#> parameter pure "AST element" "elem2" "" + =#> functionResult pushBool "boolean" "true iff elem1 == elem2" + + , defun "make_sections" + ### liftPure3 Shared.makeSections + <#> parameter peekBool "boolean" "numbering" "add header numbers" + <#> parameter (\i -> (Nothing <$ peekNil i) <|> (Just <$!> peekIntegral i)) + "integer or nil" "baselevel" "" + <#> parameter (peekList peekBlock) "list of blocks" + "blocks" "document blocks to process" + =#> functionResult pushBlocks "list of Blocks" + "processes blocks" + + , defun "normalize_date" + ### liftPure Shared.normalizeDate + <#> parameter peekText "string" "date" "the date string" + =#> functionResult (maybe pushnil pushText) "string or nil" + "normalized date, or nil if normalization failed." + #? T.unwords + [ "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" + , "or equal to 1583, but MS Word only accepts dates starting 1601)." + , "Returns nil instead of a string if the conversion failed." + ] + + , sha1 + + , defun "Version" + ### liftPure (id @Version) + <#> parameter peekVersionFuzzy + "version string, list of integers, or integer" + "v" "version description" + =#> functionResult pushVersion "Version" "new Version object" + #? "Creates a Version object." + + , defun "references" + ### (unPandocLua . getReferences Nothing) + <#> parameter peekPandoc "Pandoc" "doc" "document" + =#> functionResult (pushPandocList pushReference) "table" + "lift of references" + #? mconcat + [ "Get references defined inline in the metadata and via an external " + , "bibliography. Only references that are actually cited in the " + , "document (either with a genuine citation or with `nocite`) are " + , "returned. URL variables are converted to links." + ] + + , defun "run_json_filter" + ### (\doc filterPath margs -> do + args <- case margs of + Just xs -> return xs + Nothing -> do + Lua.getglobal "FORMAT" + (forcePeek ((:[]) <$!> peekString top) <* pop 1) + applyJSONFilter def args filterPath doc + ) + <#> parameter peekPandoc "Pandoc" "doc" "input document" + <#> parameter peekString "filepath" "filter_path" "path to filter" + <#> opt (parameter (peekList peekString) "list of strings" + "args" "arguments to pass to the filter") + =#> functionResult pushPandoc "Pandoc" "filtered document" + + , defun "stringify" + ### stringify + <#> parameter pure "AST element" "elem" "some pandoc AST element" + =#> functionResult pushText "string" "stringified element" + + , defun "from_simple_table" + ### from_simple_table + <#> parameter peekSimpleTable "SimpleTable" "simple_tbl" "" + =?> "Simple table" + + , defun "to_roman_numeral" + ### liftPure Shared.toRomanNumeral + <#> parameter (peekIntegral @Int) "integer" "n" "number smaller than 4000" + =#> functionResult pushText "string" "roman numeral" + #? "Converts a number < 4000 to uppercase roman numeral." + + , defun "to_simple_table" + ### to_simple_table + <#> parameter peekTable "Block" "tbl" "a table" + =#> functionResult pushSimpleTable "SimpleTable" "SimpleTable object" + #? "Converts a table into an old/simple table." + + , defun "type" + ### (\idx -> getmetafield idx "__name" >>= \case + TypeString -> fromMaybe mempty <$> tostring top + _ -> ltype idx >>= typename) + <#> parameter pure "any" "object" "" + =#> functionResult pushByteString "string" "type of the given value" + #? ("Pandoc-friendly version of Lua's default `type` function, " <> + "returning the type of a value. If the argument has a " <> + "string-valued metafield `__name`, then it gives that string. " <> + "Otherwise it behaves just like the normal `type` function.") + ] + } + +-- | Documented Lua function to compute the hash of a string. +sha1 :: DocumentedFunction e +sha1 = defun "sha1" + ### liftPure (SHA.showDigest . SHA.sha1) + <#> parameter (fmap BSL.fromStrict . peekByteString) "string" "input" "" + =#> functionResult pushString "string" "hexadecimal hash value" + #? "Compute the hash of the given string value." + + +-- | Convert pandoc structure to a string with formatting removed. +-- Footnotes are skipped (since we don't want their contents in link +-- labels). +stringify :: LuaError e => StackIndex -> LuaE e T.Text +stringify idx = forcePeek . retrieving "stringifyable element" $ + choice + [ (fmap Shared.stringify . peekPandoc) + , (fmap Shared.stringify . peekInline) + , (fmap Shared.stringify . peekBlock) + , (fmap Shared.stringify . peekCitation) + , (fmap stringifyMetaValue . peekMetaValue) + , (fmap (const "") . peekAttr) + , (fmap (const "") . peekListAttributes) + ] idx + where + stringifyMetaValue :: MetaValue -> T.Text + stringifyMetaValue mv = case mv of + MetaBool b -> T.toLower $ T.pack (show b) + MetaString s -> s + MetaList xs -> mconcat $ map stringifyMetaValue xs + MetaMap m -> mconcat $ map (stringifyMetaValue . snd) (Map.toList m) + _ -> Shared.stringify mv + +-- | Converts an old/simple table into a normal table block element. +from_simple_table :: SimpleTable -> LuaE PandocError NumResults +from_simple_table (SimpleTable capt aligns widths head' body) = do + Lua.push $ Table + nullAttr + (Caption Nothing [Plain capt | not (null capt)]) + (zipWith (\a w -> (a, toColWidth w)) aligns widths) + (TableHead nullAttr [blockListToRow head' | not (null head') ]) + [TableBody nullAttr 0 [] $ map blockListToRow body | not (null body)] + (TableFoot nullAttr []) + return (NumResults 1) + where + blockListToRow :: [[Block]] -> Row + blockListToRow = Row nullAttr . map (B.simpleCell . B.fromList) + + toColWidth :: Double -> ColWidth + toColWidth 0 = ColWidthDefault + toColWidth w = ColWidth w + +-- | Converts a table into an old/simple table. +to_simple_table :: Block -> LuaE PandocError SimpleTable +to_simple_table = \case + Table _attr caption specs thead tbodies tfoot -> do + let (capt, aligns, widths, headers, rows) = + Shared.toLegacyTable caption specs thead tbodies tfoot + return $ SimpleTable capt aligns widths headers rows + blk -> Lua.failLua $ mconcat + [ "Expected Table, got ", showConstr (toConstr blk), "." ] + +peekTable :: LuaError e => Peeker e Block +peekTable idx = peekBlock idx >>= \case + t@(Table {}) -> return t + b -> Lua.failPeek $ mconcat + [ "Expected Table, got " + , UTF8.fromString $ showConstr (toConstr b) + , "." ] diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs new file mode 100644 index 000000000..62b54d051 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs @@ -0,0 +1,116 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +{-# LANGUAGE FlexibleInstances #-} +{- | + Module : Text.Pandoc.Lua.Orphans + Copyright : © 2012-2022 John MacFarlane + © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +Orphan instances for Lua's Pushable and Peekable type classes. +-} +module Text.Pandoc.Lua.Orphans () where + +import Data.Version (Version) +import HsLua +import HsLua.Module.Version (peekVersionFuzzy) +import Text.Pandoc.Definition +import Text.Pandoc.Lua.Marshal.AST +import Text.Pandoc.Lua.Marshal.CommonState () +import Text.Pandoc.Lua.Marshal.Context () +import Text.Pandoc.Lua.Marshal.PandocError() +import Text.Pandoc.Lua.Marshal.ReaderOptions () +import Text.Pandoc.Lua.Marshal.Sources (pushSources) +import Text.Pandoc.Lua.ErrorConversion () +import Text.Pandoc.Sources (Sources) + +instance Pushable Pandoc where + push = pushPandoc + +instance Pushable Meta where + push = pushMeta + +instance Pushable MetaValue where + push = pushMetaValue + +instance Pushable Block where + push = pushBlock + +instance {-# OVERLAPPING #-} Pushable [Block] where + push = pushBlocks + +instance Pushable Alignment where + push = pushString . show + +instance Pushable CitationMode where + push = pushCitationMode + +instance Pushable Format where + push = pushFormat + +instance Pushable ListNumberDelim where + push = pushString . show + +instance Pushable ListNumberStyle where + push = pushString . show + +instance Pushable MathType where + push = pushMathType + +instance Pushable QuoteType where + push = pushQuoteType + +instance Pushable Cell where + push = pushCell + +instance Pushable Inline where + push = pushInline + +instance {-# OVERLAPPING #-} Pushable [Inline] where + push = pushInlines + +instance Pushable Citation where + push = pushCitation + +instance Pushable Row where + push = pushRow + +instance Pushable TableBody where + push = pushTableBody + +instance Pushable TableFoot where + push = pushTableFoot + +instance Pushable TableHead where + push = pushTableHead + +-- These instances exist only for testing. It's a hack to avoid making +-- the marshalling modules public. +instance Peekable Inline where + safepeek = peekInline + +instance Peekable Block where + safepeek = peekBlock + +instance Peekable Cell where + safepeek = peekCell + +instance Peekable Meta where + safepeek = peekMeta + +instance Peekable Pandoc where + safepeek = peekPandoc + +instance Peekable Row where + safepeek = peekRow + +instance Peekable Version where + safepeek = peekVersionFuzzy + +instance {-# OVERLAPPING #-} Peekable Attr where + safepeek = peekAttr + +instance Pushable Sources where + push = pushSources diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs new file mode 100644 index 000000000..e07a91d61 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs @@ -0,0 +1,113 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | + Module : Text.Pandoc.Lua.PandocLua + Copyright : Copyright © 2020-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + +PandocMonad instance which allows execution of Lua operations and which +uses Lua to handle state. +-} +module Text.Pandoc.Lua.PandocLua + ( PandocLua (..) + , runPandocLua + , liftPandocLua + ) where + +import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow) +import Control.Monad.Except (MonadError (catchError, throwError)) +import Control.Monad.IO.Class (MonadIO) +import HsLua as Lua +import Text.Pandoc.Class (PandocMonad (..)) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Marshal.CommonState (peekCommonState) + +import qualified Control.Monad.Catch as Catch +import qualified Text.Pandoc.Class.IO as IO + +-- | Type providing access to both, pandoc and Lua operations. +newtype PandocLua a = PandocLua { unPandocLua :: LuaE PandocError a } + deriving + ( Applicative + , Functor + , Monad + , MonadCatch + , MonadIO + , MonadMask + , MonadThrow + ) + +-- | Lift a @'Lua'@ operation into the @'PandocLua'@ type. +liftPandocLua :: LuaE PandocError a -> PandocLua a +liftPandocLua = PandocLua + +-- | Evaluate a @'PandocLua'@ computation, running all contained Lua +-- operations.. +runPandocLua :: (PandocMonad m, MonadIO m) => PandocLua a -> m a +runPandocLua pLua = do + origState <- getCommonState + globals <- defaultGlobals + (result, newState) <- liftIO . Lua.run . unPandocLua $ do + putCommonState origState + liftPandocLua $ setGlobals globals + r <- pLua + c <- getCommonState + return (r, c) + putCommonState newState + return result + +instance {-# OVERLAPPING #-} Exposable PandocError (PandocLua NumResults) where + partialApply _narg = liftLua . unPandocLua + +instance Pushable a => Exposable PandocError (PandocLua a) where + partialApply _narg x = 1 <$ (liftLua (unPandocLua x >>= Lua.push)) + +-- | Global variables which should always be set. +defaultGlobals :: PandocMonad m => m [Global] +defaultGlobals = do + commonState <- getCommonState + return + [ PANDOC_API_VERSION + , PANDOC_STATE commonState + , PANDOC_VERSION + ] + +instance MonadError PandocError PandocLua where + catchError = Catch.catch + throwError = Catch.throwM + +instance PandocMonad PandocLua where + lookupEnv = IO.lookupEnv + getCurrentTime = IO.getCurrentTime + getCurrentTimeZone = IO.getCurrentTimeZone + newStdGen = IO.newStdGen + newUniqueHash = IO.newUniqueHash + + openURL = IO.openURL + + readFileLazy = IO.readFileLazy + readFileStrict = IO.readFileStrict + readStdinStrict = IO.readStdinStrict + + glob = IO.glob + fileExists = IO.fileExists + getDataFileName = IO.getDataFileName + getModificationTime = IO.getModificationTime + + getCommonState = PandocLua $ do + Lua.getglobal "PANDOC_STATE" + forcePeek $ peekCommonState Lua.top + putCommonState = PandocLua . setGlobals . (:[]) . PANDOC_STATE + + logOutput = IO.logOutput diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs new file mode 100644 index 000000000..6303dace3 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs @@ -0,0 +1,84 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Reader + Copyright : Copyright (C) 2021-2022 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <[email protected]> + Stability : alpha + Portability : portable + +Supports custom parsers written in Lua which produce a Pandoc AST. +-} +module Text.Pandoc.Lua.Reader ( readCustom ) where +import Control.Exception +import Control.Monad (when) +import Control.Monad.IO.Class (MonadIO) +import Data.Maybe (fromMaybe) +import HsLua as Lua hiding (Operation (Div)) +import Text.Pandoc.Definition +import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback, report) +import Text.Pandoc.Logging +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Init (runLua) +import Text.Pandoc.Lua.PandocLua +import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc) +import Text.Pandoc.Options +import Text.Pandoc.Sources (ToSources(..), sourcesToText) +import qualified Data.Text as T + +-- | Convert custom markup to Pandoc. +readCustom :: (PandocMonad m, MonadIO m, ToSources s) + => FilePath -> ReaderOptions -> s -> m Pandoc +readCustom luaFile opts srcs = do + let globals = [ PANDOC_SCRIPT_FILE luaFile ] + luaFile' <- fromMaybe luaFile <$> findFileWithDataFallback "readers" luaFile + res <- runLua $ do + setGlobals globals + stat <- dofileTrace luaFile' + -- check for error in lua script (later we'll change the return type + -- to handle this more gracefully): + when (stat /= Lua.OK) + Lua.throwErrorAsException + parseCustom + case res of + Left msg -> throw msg + Right doc -> return doc + where + parseCustom = do + let input = toSources srcs + getglobal "Reader" + push input + push opts + pcallTrace 2 1 >>= \case + OK -> forcePeek $ peekPandoc top + ErrRun -> do + -- Caught a runtime error. Check if parsing might work if we + -- pass a string instead of a Sources list, then retry. + runPeek (peekText top) >>= \case + Failure {} -> + -- not a string error object. Bail! + throwErrorAsException + Success errmsg -> do + if "string expected, got pandoc Sources" `T.isInfixOf` errmsg + then do + pop 1 + _ <- unPandocLua $ do + report $ Deprecated "old Reader function signature" $ + T.unlines + [ "Reader functions should accept a sources list; " + , "functions expecting `string` input are deprecated. " + , "Use `tostring` to convert the first argument to a " + , "string." + ] + getglobal "Reader" + push $ sourcesToText input -- push sources as string + push opts + callTrace 2 1 + forcePeek $ peekPandoc top + else + -- nothing we can do here + throwErrorAsException + _ -> -- not a runtime error, we won't be able to recover from that + throwErrorAsException diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs new file mode 100644 index 000000000..f216ea63b --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Lua.Writer + Copyright : Copyright (C) 2012-2022 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <[email protected]> + Stability : alpha + Portability : portable + +Conversion of Pandoc documents using a custom Lua writer. +-} +module Text.Pandoc.Lua.Writer + ( writeCustom + ) where + +import Control.Exception +import Control.Monad ((<=<)) +import Data.Maybe (fromMaybe) +import Data.Text (Text) +import HsLua +import Control.Monad.IO.Class (MonadIO) +import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback) +import Text.Pandoc.Definition (Pandoc (..)) +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Init (runLua) +import Text.Pandoc.Options (WriterOptions) +import qualified Text.Pandoc.Lua.Writer.Classic as Classic + +-- | Convert Pandoc to custom markup. +writeCustom :: (PandocMonad m, MonadIO m) + => FilePath -> WriterOptions -> Pandoc -> m Text +writeCustom luaFile opts doc = do + luaFile' <- fromMaybe luaFile <$> findFileWithDataFallback "writers" luaFile + either throw pure <=< runLua $ do + setGlobals [ PANDOC_DOCUMENT doc + , PANDOC_SCRIPT_FILE luaFile' + , PANDOC_WRITER_OPTIONS opts + ] + dofileTrace luaFile' >>= \case + OK -> pure () + _ -> throwErrorAsException + -- Most classic writers contain code that throws an error if a global + -- is not present. This would break our check for the existence of a + -- "Writer" function. We resort to raw access for that reason, but + -- could also catch the error instead. + let rawgetglobal x = do + pushglobaltable + pushName x + rawget (nth 2) <* remove (nth 2) -- remove global table + + rawgetglobal "Writer" >>= \case + TypeNil -> do + pop 1 -- remove nil + Classic.runCustom opts doc + _ -> do + -- Writer on top of the stack. Call it with document and writer + -- options as arguments. + push doc + push opts + callTrace 2 1 + forcePeek $ peekText top diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs new file mode 100644 index 000000000..522bdb651 --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs @@ -0,0 +1,250 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Lua.Writer.Classic + Copyright : Copyright (C) 2012-2022 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <[email protected]> + Stability : alpha + Portability : portable + +Conversion of Pandoc documents using a \"classic\" custom Lua writer. +-} +module Text.Pandoc.Lua.Writer.Classic + ( runCustom + ) where +import Control.Applicative (optional) +import Control.Arrow ((***)) +import Data.List (intersperse) +import Data.Maybe (fromMaybe) +import qualified Data.Text as T +import Data.Text (Text, pack) +import HsLua as Lua hiding (Operation (Div)) +#if !MIN_VERSION_hslua(2,2,0) +import HsLua.Aeson (peekViaJSON) +#endif +import Text.DocLayout (literal, render) +import Text.DocTemplates (Context) +import Text.Pandoc.Definition +import Text.Pandoc.Lua.Marshal.Attr (pushAttributeList) +import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Options +import Text.Pandoc.Templates (renderTemplate) +import Text.Pandoc.Writers.Shared + +-- | List of key-value pairs that is pushed to Lua as AttributeList +-- userdata. +newtype AttributeList = AttributeList [(Text, Text)] +instance Pushable AttributeList where + push (AttributeList kvs) = pushAttributeList kvs + +attrToMap :: Attr -> AttributeList +attrToMap (id',classes,keyvals) = AttributeList + $ ("id", id') + : ("class", T.unwords classes) + : keyvals + +newtype Stringify a = Stringify a + +instance Pushable (Stringify Format) where + push (Stringify (Format f)) = Lua.push (T.toLower f) + +instance Pushable (Stringify [Inline]) where + push (Stringify ils) = Lua.push =<< inlineListToCustom ils + +instance Pushable (Stringify [Block]) where + push (Stringify blks) = Lua.push =<< blockListToCustom blks + +instance Pushable (Stringify MetaValue) where + push (Stringify (MetaMap m)) = Lua.push (fmap Stringify m) + push (Stringify (MetaList xs)) = Lua.push (map Stringify xs) + push (Stringify (MetaBool x)) = Lua.push x + push (Stringify (MetaString s)) = Lua.push s + push (Stringify (MetaInlines ils)) = Lua.push (Stringify ils) + push (Stringify (MetaBlocks bs)) = Lua.push (Stringify bs) + +instance Pushable (Stringify Citation) where + push (Stringify cit) = flip pushAsTable cit + [ ("citationId", push . citationId) + , ("citationPrefix", push . Stringify . citationPrefix) + , ("citationSuffix", push . Stringify . citationSuffix) + , ("citationMode", push . citationMode) + , ("citationNoteNum", push . citationNoteNum) + , ("citationHash", push . citationHash) + ] + +-- | Key-value pair, pushed as a table with @a@ as the only key and @v@ as the +-- associated value. +newtype KeyValue a b = KeyValue (a, b) + +instance (Pushable a, Pushable b) => Pushable (KeyValue a b) where + push (KeyValue (k, v)) = do + Lua.newtable + Lua.push k + Lua.push v + Lua.rawset (Lua.nth 3) + +-- | Convert Pandoc to custom markup using a classic Lua writer. +runCustom :: LuaError e + => WriterOptions + -> Pandoc + -> LuaE e Text +runCustom opts doc@(Pandoc meta _) = do + (body, context) <- docToCustom opts doc + -- convert metavalues to a template context (variables) + metaContext <- metaToContext opts + (fmap (literal . pack) . blockListToCustom) + (fmap (literal . pack) . inlineListToCustom) + meta + -- merge contexts from metadata and variables + let renderContext = context <> metaContext + return $ case writerTemplate opts of + Nothing -> body + Just tpl -> render Nothing $ + renderTemplate tpl $ setField "body" body renderContext + +-- | Converts a Pandoc value to custom markup using a classic Lua writer. +docToCustom :: forall e. LuaError e + => WriterOptions -> Pandoc -> LuaE e (Text, Context Text) +docToCustom opts (Pandoc (Meta metamap) blocks) = do + body <- blockListToCustom blocks + -- invoke doesn't work with multiple return values, so we have to call + -- `Doc` manually. + Lua.getglobal "Doc" -- function + push body -- argument 1 + push (fmap Stringify metamap) -- argument 2 + push (writerVariables opts) -- argument 3 + call 3 2 + rendered <- peek (nth 2) -- first return value + context <- forcePeek . optional $ peekViaJSON top -- snd return value + return (rendered, fromMaybe mempty context) + + +-- | Convert Pandoc block element to Custom. +blockToCustom :: forall e. LuaError e + => Block -- ^ Block element + -> LuaE e String + +blockToCustom Null = return "" + +blockToCustom (Plain inlines) = invoke "Plain" (Stringify inlines) + +blockToCustom (Para [Image attr txt (src,tit)]) = + invoke "CaptionedImage" src tit (Stringify txt) (attrToMap attr) + +blockToCustom (Para inlines) = invoke "Para" (Stringify inlines) + +blockToCustom (LineBlock linesList) = + invoke "LineBlock" (map (Stringify) linesList) + +blockToCustom (RawBlock format str) = + invoke "RawBlock" (Stringify format) str + +blockToCustom HorizontalRule = invoke "HorizontalRule" + +blockToCustom (Header level attr inlines) = + invoke "Header" level (Stringify inlines) (attrToMap attr) + +blockToCustom (CodeBlock attr str) = + invoke "CodeBlock" str (attrToMap attr) + +blockToCustom (BlockQuote blocks) = + invoke "BlockQuote" (Stringify blocks) + +blockToCustom (Table _ blkCapt specs thead tbody tfoot) = + let (capt, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + aligns' = map show aligns + capt' = Stringify capt + headers' = map (Stringify) headers + rows' = map (map (Stringify)) rows + in invoke "Table" capt' aligns' widths headers' rows' + +blockToCustom (BulletList items) = + invoke "BulletList" (map (Stringify) items) + +blockToCustom (OrderedList (num,sty,delim) items) = + invoke "OrderedList" (map (Stringify) items) num (show sty) (show delim) + +blockToCustom (DefinitionList items) = + invoke "DefinitionList" + (map (KeyValue . (Stringify *** map (Stringify))) items) + +blockToCustom (Div attr items) = + invoke "Div" (Stringify items) (attrToMap attr) + +-- | Convert list of Pandoc block elements to Custom. +blockListToCustom :: forall e. LuaError e + => [Block] -- ^ List of block elements + -> LuaE e String +blockListToCustom xs = do + blocksep <- invoke "Blocksep" + bs <- mapM blockToCustom xs + return $ mconcat $ intersperse blocksep bs + +-- | Convert list of Pandoc inline elements to Custom. +inlineListToCustom :: forall e. LuaError e => [Inline] -> LuaE e String +inlineListToCustom lst = do + xs <- mapM (inlineToCustom @e) lst + return $ mconcat xs + +-- | Convert Pandoc inline element to Custom. +inlineToCustom :: forall e. LuaError e => Inline -> LuaE e String + +inlineToCustom (Str str) = invoke "Str" str + +inlineToCustom Space = invoke "Space" + +inlineToCustom SoftBreak = invoke "SoftBreak" + +inlineToCustom (Emph lst) = invoke "Emph" (Stringify lst) + +inlineToCustom (Underline lst) = invoke "Underline" (Stringify lst) + +inlineToCustom (Strong lst) = invoke "Strong" (Stringify lst) + +inlineToCustom (Strikeout lst) = invoke "Strikeout" (Stringify lst) + +inlineToCustom (Superscript lst) = invoke "Superscript" (Stringify lst) + +inlineToCustom (Subscript lst) = invoke "Subscript" (Stringify lst) + +inlineToCustom (SmallCaps lst) = invoke "SmallCaps" (Stringify lst) + +inlineToCustom (Quoted SingleQuote lst) = + invoke "SingleQuoted" (Stringify lst) + +inlineToCustom (Quoted DoubleQuote lst) = + invoke "DoubleQuoted" (Stringify lst) + +inlineToCustom (Cite cs lst) = + invoke "Cite" (Stringify lst) (map (Stringify) cs) + +inlineToCustom (Code attr str) = + invoke "Code" str (attrToMap attr) + +inlineToCustom (Math DisplayMath str) = + invoke "DisplayMath" str + +inlineToCustom (Math InlineMath str) = + invoke "InlineMath" str + +inlineToCustom (RawInline format str) = + invoke "RawInline" (Stringify format) str + +inlineToCustom LineBreak = invoke "LineBreak" + +inlineToCustom (Link attr txt (src,tit)) = + invoke "Link" (Stringify txt) src tit (attrToMap attr) + +inlineToCustom (Image attr alt (src,tit)) = + invoke "Image" (Stringify alt) src tit (attrToMap attr) + +inlineToCustom (Note contents) = invoke "Note" (Stringify contents) + +inlineToCustom (Span attr items) = + invoke "Span" (Stringify items) (attrToMap attr) diff --git a/pandoc-lua-engine/test/Tests/Lua.hs b/pandoc-lua-engine/test/Tests/Lua.hs new file mode 100644 index 000000000..6f544ccd4 --- /dev/null +++ b/pandoc-lua-engine/test/Tests/Lua.hs @@ -0,0 +1,246 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Tests.Lua + Copyright : © 2017-2022 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <[email protected]> + Stability : alpha + Portability : portable + +Unit and integration tests for pandoc's Lua subsystem. +-} +module Tests.Lua ( runLuaTest, tests ) where + +import HsLua as Lua hiding (Operation (Div), error) +import System.FilePath ((</>)) +import Test.Tasty (TestTree, testGroup) +import Test.Tasty.HUnit ((@=?), Assertion, HasCallStack, assertEqual, testCase) +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith, + doc, doubleQuoted, emph, header, lineBlock, + linebreak, math, orderedList, para, plain, rawBlock, + singleQuoted, space, str, strong, + HasMeta (setMeta)) +import Text.Pandoc.Class (runIOorExplode, setUserDataDir) +import Text.Pandoc.Definition (Attr, Block (BlockQuote, Div, Para), Pandoc, + Inline (Emph, Str), pandocTypesVersion) +import Text.Pandoc.Error (PandocError (PandocLuaError)) +import Text.Pandoc.Lua (Global (..), applyFilter, runLua, setGlobals) +import Text.Pandoc.Options (def) +import Text.Pandoc.Shared (pandocVersionText) + +import qualified Control.Monad.Catch as Catch +import qualified Data.Text as T +import qualified Data.Text.Encoding as TE + +tests :: [TestTree] +tests = + [ testCase "macro expansion via filter" $ + assertFilterConversion "a '{{helloworld}}' string is expanded" + "strmacro.lua" + (doc . para $ str "{{helloworld}}") + (doc . para . emph $ str "Hello, World") + + , testCase "convert all plains to paras" $ + assertFilterConversion "plains become para" + "plain-to-para.lua" + (doc $ bulletList [plain (str "alfa"), plain (str "bravo")]) + (doc $ bulletList [para (str "alfa"), para (str "bravo")]) + + , testCase "convert display math to inline math" $ + assertFilterConversion "display math becomes inline math" + "math.lua" + (doc $ para (displayMath "5+5")) + (doc $ para (math "5+5")) + + , testCase "make hello world document" $ + assertFilterConversion "Document contains 'Hello, World!'" + "hello-world-doc.lua" + (doc . para $ str "Hey!" <> linebreak <> str "What's up?") + (doc . para $ str "Hello," <> space <> str "World!") + + , testCase "implicit doc filter" $ + assertFilterConversion "Document contains 'Hello, World!'" + "implicit-doc-filter.lua" + (doc . plain $ linebreak) + (doc . para $ str "Hello," <> space <> str "World!") + + , testCase "parse raw markdown blocks" $ + assertFilterConversion "raw markdown block is converted" + "markdown-reader.lua" + (doc $ rawBlock "markdown" "*charly* **delta**") + (doc . para $ emph "charly" <> space <> strong "delta") + + , testCase "allow shorthand functions for quote types" $ + assertFilterConversion "single quoted becomes double quoted string" + "single-to-double-quoted.lua" + (doc . para . singleQuoted $ str "simple") + (doc . para . doubleQuoted $ str "simple") + + , testCase "Count inlines via metatable catch-all" $ + assertFilterConversion "filtering with metatable catch-all failed" + "metatable-catch-all.lua" + (doc . para $ "four words, three spaces") + (doc . para $ str "7") + + , testCase "Count blocks via Block-specific catch-all" $ + assertFilterConversion "filtering with Block catch-all failed" + "block-count.lua" + (doc $ para "one" <> para "two") + (doc $ para "2") + + , testCase "Smart constructors" $ + assertFilterConversion "smart constructors returned a wrong result" + "smart-constructors.lua" + (doc $ para "") + (doc $ mconcat + [ bulletList [para "Hello", para "World"] + , definitionList [("foo", [para "placeholder"])] + , lineBlock ["Moin", "Welt"] + , orderedList [plain "one", plain "two"] + ]) + + , testCase "Convert header upper case" $ + assertFilterConversion "converting header to upper case failed" + "uppercase-header.lua" + (doc $ header 1 "les états-unis" <> para "text") + (doc $ header 1 "LES ÉTATS-UNIS" <> para "text") + + , testCase "Attribute lists are convenient to use" $ + let kv_before = [("one", "1"), ("two", "2"), ("three", "3")] + kv_after = [("one", "eins"), ("three", "3"), ("five", "5")] + in assertFilterConversion "Attr doesn't behave as expected" + "attr-test.lua" + (doc $ divWith ("", [], kv_before) (para "nil")) + (doc $ divWith ("", [], kv_after) (para "nil")) + + , testCase "Filter list of inlines" $ + assertFilterConversion "List of inlines" + "inlines-filter.lua" + (doc $ para ("Hello," <> linebreak <> "World! Wassup?")) + (doc $ para "Hello, World! Wassup?") + + , testCase "Filter list of blocks" $ + assertFilterConversion "List of blocks" + "blocks-filter.lua" + (doc $ para "one." <> para "two." <> para "three.") + (doc $ plain "3") + + , testCase "Filter Meta" $ + let setMetaBefore = setMeta "old" ("old" :: T.Text) + . setMeta "bool" False + setMetaAfter = setMeta "new" ("new" :: T.Text) + . setMeta "bool" True + in assertFilterConversion "Meta filtering" + "meta.lua" + (setMetaBefore . doc $ mempty) + (setMetaAfter . doc $ mempty) + + , testCase "Script filename is set" $ + assertFilterConversion "unexpected script name" + "script-name.lua" + (doc $ para "ignored") + (doc $ para (str $ T.pack $ "lua" </> "script-name.lua")) + + , testCase "Pandoc version is set" . runLuaTest $ do + Lua.getglobal "PANDOC_VERSION" + Lua.liftIO . + assertEqual "pandoc version is wrong" (TE.encodeUtf8 pandocVersionText) + =<< Lua.tostring' Lua.top + + , testCase "Pandoc types version is set" . runLuaTest $ do + Lua.getglobal "PANDOC_API_VERSION" + Lua.liftIO . assertEqual "pandoc-types version is wrong" pandocTypesVersion + =<< Lua.peek Lua.top + + , testCase "require file" $ + assertFilterConversion "requiring file failed" + "require-file.lua" + (doc $ para "ignored") + (doc $ para (str . T.pack $ "lua" </> "require-file.lua")) + + , testCase "Allow singleton inline in constructors" . runLuaTest $ do + Lua.liftIO . assertEqual "Not the expected Emph" + (Emph [Str "test"]) =<< do + Lua.OK <- Lua.dostring "return pandoc.Emph" + Lua.push @Inline (Str "test") + Lua.call 1 1 + Lua.peek @Inline top + Lua.liftIO . assertEqual "Unexpected element" + (Para [Str "test"]) =<< do + Lua.getglobal' "pandoc.Para" + Lua.pushString "test" + Lua.call 1 1 + Lua.peek @Block top + Lua.liftIO . assertEqual "Unexptected element" + (BlockQuote [Para [Str "foo"]]) =<< ( + do + Lua.getglobal' "pandoc.BlockQuote" + Lua.push (Para [Str "foo"]) + _ <- Lua.call 1 1 + Lua.peek @Block Lua.top + ) + + , testCase "Elements with Attr have `attr` accessor" . runLuaTest $ do + Lua.push (Div ("hi", ["moin"], []) + [Para [Str "ignored"]]) + Lua.getfield Lua.top "attr" + Lua.liftIO . assertEqual "no accessor" (("hi", ["moin"], []) :: Attr) + =<< Lua.peek @Attr Lua.top + + , testCase "module `pandoc.system` is present" . runLuaTest $ do + Lua.getglobal' "pandoc.system" + ty <- Lua.ltype Lua.top + Lua.liftIO $ assertEqual "module should be a table" Lua.TypeTable ty + + , testGroup "global modules" + [ testCase "module 'lpeg' is loaded into a global" . runLuaTest $ do + s <- Lua.dostring "assert(type(lpeg)=='table')" + Lua.liftIO $ Lua.OK @=? s + + , testCase "module 're' is loaded into a global" . runLuaTest $ do + s <- Lua.dostring "assert(type(re)=='table')" + Lua.liftIO $ Lua.OK @=? s + + , testCase "module 'lpeg' is available via `require`" . runLuaTest $ do + s <- Lua.dostring + "package.path = ''; package.cpath = ''; require 'lpeg'" + Lua.liftIO $ Lua.OK @=? s + + , testCase "module 're' is available via `require`" . runLuaTest $ do + s <- Lua.dostring + "package.path = ''; package.cpath = ''; require 're'" + Lua.liftIO $ Lua.OK @=? s + ] + + , testCase "informative error messages" . runLuaTest $ do + Lua.pushboolean True + -- Lua.newtable + eitherPandoc <- Catch.try (peek @Pandoc Lua.top) + case eitherPandoc of + Left (PandocLuaError msg) -> do + let expectedMsg = "Pandoc expected, got boolean\n" + <> "\twhile retrieving Pandoc" + Lua.liftIO $ assertEqual "unexpected error message" expectedMsg msg + Left e -> error ("Expected a Lua error, but got " <> show e) + Right _ -> error "Getting a Pandoc element from a bool should fail." + ] + +assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion +assertFilterConversion msg filterPath docIn expectedDoc = do + actualDoc <- runIOorExplode $ do + setUserDataDir (Just "../data") + applyFilter def ["HTML"] ("lua" </> filterPath) docIn + assertEqual msg expectedDoc actualDoc + +runLuaTest :: HasCallStack => Lua.LuaE PandocError a -> IO a +runLuaTest op = runIOorExplode $ do + res <- runLua $ do + setGlobals [ PANDOC_WRITER_OPTIONS def ] + op + case res of + Left e -> error (show e) + Right x -> return x diff --git a/pandoc-lua-engine/test/Tests/Lua/Module.hs b/pandoc-lua-engine/test/Tests/Lua/Module.hs new file mode 100644 index 000000000..fd3fc8998 --- /dev/null +++ b/pandoc-lua-engine/test/Tests/Lua/Module.hs @@ -0,0 +1,41 @@ +{- | +Module : Tests.Lua.Module +Copyright : © 2019-2022 Albert Krewinkel +License : GNU GPL, version 2 or above + +Maintainer : Albert Krewinkel <[email protected]> +Stability : alpha +Portability : portable + +Lua module tests +-} +module Tests.Lua.Module (tests) where + +import System.FilePath ((</>)) +import Test.Tasty (TestName, TestTree) +import Test.Tasty.Lua (testLuaFile) + +import Tests.Lua (runLuaTest) + +tests :: [TestTree] +tests = + [ testPandocLua "pandoc" + ("lua" </> "module" </> "pandoc.lua") + , testPandocLua "pandoc.List" + ("lua" </> "module" </> "pandoc-list.lua") + , testPandocLua "pandoc.mediabag" + ("lua" </> "module" </> "pandoc-mediabag.lua") + , testPandocLua "pandoc.path" + ("lua" </> "module" </> "pandoc-path.lua") + , testPandocLua "pandoc.template" + ("lua" </> "module" </> "pandoc-template.lua") + , testPandocLua "pandoc.types" + ("lua" </> "module" </> "pandoc-types.lua") + , testPandocLua "pandoc.utils" + ("lua" </> "module" </> "pandoc-utils.lua") + , testPandocLua "globals" + ("lua" </> "module" </> "globals.lua") + ] + +testPandocLua :: TestName -> FilePath -> TestTree +testPandocLua = testLuaFile runLuaTest diff --git a/pandoc-lua-engine/test/Tests/Lua/Writer.hs b/pandoc-lua-engine/test/Tests/Lua/Writer.hs new file mode 100644 index 000000000..4086b9768 --- /dev/null +++ b/pandoc-lua-engine/test/Tests/Lua/Writer.hs @@ -0,0 +1,41 @@ +{- | +Module : Tests.Lua.Writer +Copyright : © 2019-2022 Albert Krewinkel +License : GNU GPL, version 2 or above + +Maintainer : Albert Krewinkel <[email protected]> +Stability : alpha +Portability : portable + +Tests for custom Lua writers. +-} +module Tests.Lua.Writer (tests) where + +import Data.Default (Default (def)) +import Text.Pandoc.Class (runIOorExplode, readFileStrict) +import Text.Pandoc.Lua (writeCustom) +import Text.Pandoc.Readers (readNative) +import Test.Tasty (TestTree) +import Test.Tasty.Golden (goldenVsString) + +import qualified Data.ByteString.Lazy as BL +import qualified Text.Pandoc.UTF8 as UTF8 + +tests :: [TestTree] +tests = + [ goldenVsString "default testsuite" + "writer.custom" + (runIOorExplode $ do + source <- UTF8.toText <$> readFileStrict "testsuite.native" + doc <- readNative def source + txt <- writeCustom "sample.lua" def doc + pure $ BL.fromStrict (UTF8.fromText txt)) + + , goldenVsString "tables testsuite" + "tables.custom" + (runIOorExplode $ do + source <- UTF8.toText <$> readFileStrict "tables.native" + doc <- readNative def source + txt <- writeCustom "sample.lua" def doc + pure $ BL.fromStrict (UTF8.fromText txt)) + ] diff --git a/pandoc-lua-engine/test/lua/attr-test.lua b/pandoc-lua-engine/test/lua/attr-test.lua new file mode 100644 index 000000000..68dc0012d --- /dev/null +++ b/pandoc-lua-engine/test/lua/attr-test.lua @@ -0,0 +1,6 @@ +function Div (div) + div.attributes.five = ("%d"):format(div.attributes.two + div.attributes.three) + div.attributes.two = nil + div.attributes.one = "eins" + return div +end diff --git a/pandoc-lua-engine/test/lua/block-count.lua b/pandoc-lua-engine/test/lua/block-count.lua new file mode 100644 index 000000000..508b05ea8 --- /dev/null +++ b/pandoc-lua-engine/test/lua/block-count.lua @@ -0,0 +1,11 @@ +local num_blocks = 0 + +function Block(el) + num_blocks = num_blocks + 1 +end + +function Pandoc(blocks, meta) + return pandoc.Pandoc { + pandoc.Para{pandoc.Str(num_blocks)} + } +end diff --git a/pandoc-lua-engine/test/lua/blocks-filter.lua b/pandoc-lua-engine/test/lua/blocks-filter.lua new file mode 100644 index 000000000..4e944e922 --- /dev/null +++ b/pandoc-lua-engine/test/lua/blocks-filter.lua @@ -0,0 +1,8 @@ +function Blocks (blks) + -- verify that this looks like a `pandoc.List` + if not blks.find or not blks.map or not blks.filter then + error("table doesn't seem to be an instance of pandoc.List") + end + -- return plain block containing the number of elements in the list + return {pandoc.Plain {pandoc.Str(tostring(#blks))}} +end diff --git a/pandoc-lua-engine/test/lua/hello-world-doc.lua b/pandoc-lua-engine/test/lua/hello-world-doc.lua new file mode 100644 index 000000000..62236584e --- /dev/null +++ b/pandoc-lua-engine/test/lua/hello-world-doc.lua @@ -0,0 +1,10 @@ +return { + { + Pandoc = function(doc) + local meta = {} + local hello = { pandoc.Str "Hello,", pandoc.Space(), pandoc.Str "World!" } + local blocks = { pandoc.Para(hello) } + return pandoc.Pandoc(blocks, meta) + end + } +} diff --git a/pandoc-lua-engine/test/lua/implicit-doc-filter.lua b/pandoc-lua-engine/test/lua/implicit-doc-filter.lua new file mode 100644 index 000000000..f053dc1b2 --- /dev/null +++ b/pandoc-lua-engine/test/lua/implicit-doc-filter.lua @@ -0,0 +1,6 @@ +function Pandoc (doc) + local meta = {} + local hello = { pandoc.Str "Hello,", pandoc.Space(), pandoc.Str "World!" } + local blocks = { pandoc.Para(hello) } + return pandoc.Pandoc(blocks, meta) +end diff --git a/pandoc-lua-engine/test/lua/inlines-filter.lua b/pandoc-lua-engine/test/lua/inlines-filter.lua new file mode 100644 index 000000000..69608bd77 --- /dev/null +++ b/pandoc-lua-engine/test/lua/inlines-filter.lua @@ -0,0 +1,19 @@ +function isWorldAfterSpace (fst, snd) + return fst and fst.t == 'LineBreak' + and snd and snd.t == 'Str' and snd.text == 'World!' +end + +function Inlines (inlns) + -- verify that this looks like a `pandoc.List` + if not inlns.find or not inlns.map or not inlns.filter then + error("table doesn't seem to be an instance of pandoc.List") + end + + -- Remove spaces before string "World" + for i = #inlns-1,1,-1 do + if isWorldAfterSpace(inlns[i], inlns[i+1]) then + inlns[i] = pandoc.Space() + end + end + return inlns +end diff --git a/pandoc-lua-engine/test/lua/markdown-reader.lua b/pandoc-lua-engine/test/lua/markdown-reader.lua new file mode 100644 index 000000000..1530a15a2 --- /dev/null +++ b/pandoc-lua-engine/test/lua/markdown-reader.lua @@ -0,0 +1,12 @@ +return { + { + RawBlock = function (elem) + if elem.format == "markdown" then + local pd = pandoc.read(elem.text, "markdown") + return pd.blocks[1] + else + return elem + end + end, + } +} diff --git a/pandoc-lua-engine/test/lua/math.lua b/pandoc-lua-engine/test/lua/math.lua new file mode 100644 index 000000000..34307dd9e --- /dev/null +++ b/pandoc-lua-engine/test/lua/math.lua @@ -0,0 +1,10 @@ +return { + { + Math = function (elem) + if elem.mathtype == "DisplayMath" then + elem.mathtype = "InlineMath" + end + return elem + end, + } +} diff --git a/pandoc-lua-engine/test/lua/meta.lua b/pandoc-lua-engine/test/lua/meta.lua new file mode 100644 index 000000000..5e2946203 --- /dev/null +++ b/pandoc-lua-engine/test/lua/meta.lua @@ -0,0 +1,6 @@ +function Meta (meta) + meta.old = nil + meta.new = "new" + meta.bool = (meta.bool == false) + return meta +end diff --git a/pandoc-lua-engine/test/lua/metatable-catch-all.lua b/pandoc-lua-engine/test/lua/metatable-catch-all.lua new file mode 100644 index 000000000..05df16bbf --- /dev/null +++ b/pandoc-lua-engine/test/lua/metatable-catch-all.lua @@ -0,0 +1,20 @@ +local num_inlines = 0 + +function catch_all(el) + if el.tag and pandoc.Inline.constructor[el.tag] then + num_inlines = num_inlines + 1 + end +end + +function Pandoc(blocks, meta) + return pandoc.Pandoc { + pandoc.Para{pandoc.Str(num_inlines)} + } +end + +return { + setmetatable( + {Pandoc = Pandoc}, + {__index = function(_) return catch_all end} + ) +} diff --git a/pandoc-lua-engine/test/lua/module/globals.lua b/pandoc-lua-engine/test/lua/module/globals.lua new file mode 100644 index 000000000..85b287cf2 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/globals.lua @@ -0,0 +1,108 @@ +local tasty = require 'tasty' + +local test = tasty.test_case +local group = tasty.test_group +local assert = tasty.assert + +-- These tests exist mainly to catch changes to the JSON representation of +-- WriterOptions and its components. UPDATE THE DOCS if anything changes. +return { + group 'PANDOC_WRITER_OPTIONS' { + test('cite_method', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.cite_method), 'string') + end), + test('columns', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.columns), 'number') + end), + test('dpi', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.dpi), 'number') + end), + test('email_obfuscation', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.email_obfuscation), 'string') + end), + test('epub_chapter_level', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.epub_chapter_level), 'number') + end), + test('epub_fonts', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.epub_fonts), 'table') + end), + test('epub_metadata', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.epub_metadata), 'nil') + end), + test('epub_subdirectory', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.epub_subdirectory), 'string') + end), + test('extensions', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.extensions), 'table') + for _, v in ipairs(PANDOC_WRITER_OPTIONS.extensions) do + assert.are_equal(type(v), 'string') + end + end), + test('highlight_style', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.highlight_style), 'table') + end), + test('html_math_method', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.html_math_method), 'string') + end), + test('html_q_tags', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.html_q_tags), 'boolean') + end), + test('identifier_prefix', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.identifier_prefix), 'string') + end), + test('incremental', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.incremental), 'boolean') + end), + test('listings', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.listings), 'boolean') + end), + test('number_offset', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.number_offset), 'table') + for _, v in ipairs(PANDOC_WRITER_OPTIONS.number_offset) do + assert.are_equal(type(v), 'number') + end + end), + test('number_sections', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.number_sections), 'boolean') + end), + test('prefer_ascii', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.prefer_ascii), 'boolean') + end), + test('reference_doc', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.reference_doc), 'nil') + end), + test('reference_links', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.reference_links), 'boolean') + end), + test('reference_location', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.reference_location), 'string') + end), + test('section_divs', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.section_divs), 'boolean') + end), + test('setext_headers', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.setext_headers), 'boolean') + end), + test('slide_level', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.slide_level), 'nil') + end), + test('tab_stop', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.tab_stop), 'number') + end), + test('table_of_contents', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.table_of_contents), 'boolean') + end), + test('toc_depth', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.toc_depth), 'number') + end), + test('top_level_division', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.top_level_division), 'string') + end), + test('variables', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.variables), 'table') + end), + test('wrap_text', function () + assert.are_equal(type(PANDOC_WRITER_OPTIONS.wrap_text), 'string') + end), + } +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-list.lua b/pandoc-lua-engine/test/lua/module/pandoc-list.lua new file mode 100644 index 000000000..27790ce96 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-list.lua @@ -0,0 +1,160 @@ +local tasty = require 'tasty' +local List = require 'pandoc.List' + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'List as function' { + test('equivalent to List:new', function (x) + local new = List:new {'ramen'} + local list = List {'ramen'} + assert.are_same(new, list) + assert.are_equal(getmetatable(new), getmetatable(list)) + end) + }, + + group 'clone' { + test('changing the clone does not affect original', function () + local orig = List:new {23, 42} + local copy = orig:clone() + copy[1] = 5 + assert.are_same({23, 42}, orig) + assert.are_same({5, 42}, copy) + end), + test('result is a list', function () + local orig = List:new {23, 42} + assert.are_equal(List, getmetatable(orig:clone())) + end), + }, + + group 'extend' { + test('extends list with other list', function () + local primes = List:new {2, 3, 5, 7} + primes:extend {11, 13, 17} + assert.are_same({2, 3, 5, 7, 11, 13, 17}, primes) + end) + }, + + group 'filter' { + test('keep elements for which property is truthy', function () + local is_small_prime = function (x) + return List.includes({2, 3, 5, 7}, x) + end + local numbers = List:new {4, 7, 2, 9, 5, 11} + assert.are_same({7, 2, 5}, numbers:filter(is_small_prime)) + end), + }, + + group 'find' { + test('returns element and index if found', function () + local list = List:new {5, 23, 71} + local elem, idx = list:find(71) + assert.are_same(71, elem) + assert.are_same(3, idx) + end), + test('respects start index', function () + local list = List:new {19, 23, 29, 71} + assert.are_equal(23, list:find(23, 1)) + assert.are_equal(23, list:find(23, 2)) + assert.is_nil(list:find(23, 3)) + end), + test('returns nil if element not found', function () + assert.is_nil((List:new {18, 20, 22, 0, 24}):find('0')) + end), + }, + + group 'find_if' { + test('returns element and index if found', function () + local perm_prime = List:new {2, 3, 5, 7, 11, 13, 17, 31, 37, 71} + local elem, idx = perm_prime:find_if(function (x) return x >= 10 end) + assert.are_same(11, elem) + assert.are_same(5, idx) + end), + test('returns nil if element not found', function () + local is_null = function (n) return List.includes({23,35,46,59}, n) end + assert.is_nil((List:new {18, 20, 22, 24, 27}):find_if(is_null)) + end), + }, + + group 'includes' { + test('finds elements in list', function () + local lst = List:new {'one', 'two', 'three'} + assert.is_truthy(lst:includes('one')) + assert.is_truthy(lst:includes('two')) + assert.is_truthy(lst:includes('three')) + assert.is_falsy(lst:includes('four')) + end) + }, + + group 'insert' { + test('insert value at end of list.', function () + local count_norsk = List {'en', 'to', 'tre'} + count_norsk:insert('fire') + assert.are_same({'en', 'to', 'tre', 'fire'}, count_norsk) + end), + test('insert value in the middle of list.', function () + local count_norsk = List {'fem', 'syv'} + count_norsk:insert(2, 'seks') + assert.are_same({'fem', 'seks', 'syv'}, count_norsk) + end) + }, + + group 'map' { + test('applies function to elements', function () + local primes = List:new {2, 3, 5, 7} + local squares = primes:map(function (x) return x^2 end) + assert.are_same({4, 9, 25, 49}, squares) + end), + test('leaves original list unchanged', function () + local primes = List:new {2, 3, 5, 7} + local squares = primes:map(function (x) return x^2 end) + assert.are_same({2, 3, 5, 7}, primes) + end) + }, + + group 'new' { + test('make table usable as list', function () + local test = List:new{1, 1, 2, 3, 5} + assert.are_same( + {1, 1, 4, 9, 25}, + test:map(function (x) return x^2 end) + ) + end), + test('return empty list if no argument is given', function () + assert.are_same({}, List:new()) + end), + test('metatable of result is pandoc.List', function () + local test = List:new{5} + assert.are_equal(List, getmetatable(test)) + end) + }, + + group 'remove' { + test('remove value at end of list.', function () + local understand = List {'jeg', 'forstår', 'ikke'} + local norsk_not = understand:remove() + assert.are_same({'jeg', 'forstår'}, understand) + assert.are_equal('ikke', norsk_not) + end), + test('remove value at beginning of list.', function () + local count_norsk = List {'en', 'to', 'tre'} + count_norsk:remove(1) + assert.are_same({'to', 'tre'}, count_norsk) + end) + }, + + group 'sort' { + test('sort numeric list', function () + local numbers = List {71, 5, -1, 42, 23, 0, 1} + numbers:sort() + assert.are_same({-1, 0, 1, 5, 23, 42, 71}, numbers) + end), + test('reverse-sort numeric', function () + local numbers = List {71, 5, -1, 42, 23, 0, 1} + numbers:sort(function (x, y) return x > y end) + assert.are_same({71, 42, 23, 5, 1, 0, -1}, numbers) + end) + }, +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-mediabag.lua b/pandoc-lua-engine/test/lua/module/pandoc-mediabag.lua new file mode 100644 index 000000000..5ff65ee44 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-mediabag.lua @@ -0,0 +1,72 @@ +local tasty = require 'tasty' + +local test = tasty.test_case +local group = tasty.test_group +local assert = tasty.assert + +local mediabag = require 'pandoc.mediabag' + +return { + group 'insert' { + test('insert adds an item to the mediabag', function () + local fp = "media/hello.txt" + local mt = "text/plain" + local contents = "Hello, World!" + assert.are_same(mediabag.list(), {}) + mediabag.insert(fp, mt, contents) + assert.are_same( + mediabag.list(), + {{['path'] = fp, ['type'] = mt, ['length'] = 13}} + ) + mediabag.empty() -- clean up + end), + test('is idempotent', function () + local fp = "media/hello.txt" + local mt = "text/plain" + local contents = "Hello, World!" + mediabag.insert(fp, mt, contents) + mediabag.insert(fp, mt, contents) + assert.are_same( + mediabag.list(), + {{['path'] = fp, ['type'] = mt, ['length'] = 13}} + ) + mediabag.empty() -- clean up + end), + }, + + group 'delete' { + test('removes an item', function () + assert.are_same(mediabag.list(), {}) + mediabag.insert('test.html', 'text/html', '<aside>Who cares?</aside>') + mediabag.insert('test.css', 'text/plain', 'aside { color: red; }') + assert.are_equal(#mediabag.list(), 2) + mediabag.delete('test.html') + assert.are_same( + mediabag.list(), + {{['path'] = 'test.css', ['type'] = 'text/plain', ['length'] = 21}} + ) + mediabag.empty() -- clean up + end), + }, + + group 'items' { + test('iterates over all items', function () + local input_items = { + ['test.html'] = {'text/html', '<aside>Really?</aside>'}, + ['test.css'] = {'text/plain', 'aside { color: red; }'}, + ['test.js'] = {'application/javascript', 'alert("HI MOM!")'} + } + -- fill mediabag + for name, v in pairs(input_items) do + mediabag.insert(name, v[1], v[2]) + end + + local seen_items = {} + for fp, mt, c in mediabag.items() do + seen_items[fp] = {mt, c} + end + assert.are_same(seen_items, input_items) + mediabag.empty() -- clean up + end) + } +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-path.lua b/pandoc-lua-engine/test/lua/module/pandoc-path.lua new file mode 100644 index 000000000..81c11e7b7 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-path.lua @@ -0,0 +1,44 @@ +local tasty = require 'tasty' +local path = require 'pandoc.path' + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'path separator' { + test('is string', function () + assert.are_same(type(path.separator), 'string') + end), + test('is slash or backslash', function () + assert.is_truthy(path.separator:match '^[/\\]$') + end), + }, + group 'search path separator' { + test('is string', function () + assert.are_same(type(path.search_path_separator), 'string') + end), + test('is colon or semicolon', function () + assert.is_truthy(path.search_path_separator:match '^[:;]$') + end) + }, + group 'module' { + test('check function existence', function () + local functions = { + 'directory', + 'filename', + 'is_absolute', + 'is_relative', + 'join', + 'make_relative', + 'normalize', + 'split', + 'split_extension', + 'split_search_path', + } + for _, f in ipairs(functions) do + assert.are_equal(type(path[f]), 'function') + end + end) + } +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-template.lua b/pandoc-lua-engine/test/lua/module/pandoc-template.lua new file mode 100644 index 000000000..c288b2016 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-template.lua @@ -0,0 +1,65 @@ +local tasty = require 'tasty' +local template = require 'pandoc.template' + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + test('is table', function () + assert.are_equal(type(template), 'table') + end), + group 'default' { + test('is function', function () + assert.are_equal(type(template.default), 'function') + end), + test('returns a string for known format', function () + assert.are_equal( + pandoc.utils.type(template.default 'json'), + 'string' + ) + assert.are_equal( + pandoc.utils.type(template.default 'markdown'), + 'string' + ) + end), + test('fails on unknown format', function () + local success, msg = pcall(function () + return pandoc.utils.type(template.default 'nosuchformat') + end) + assert.is_falsy(success) + end), + }, + group 'compile' { + test('is function', function () + assert.are_equal(type(template.compile), 'function') + end), + test('returns a Template', function () + assert.are_equal( + pandoc.utils.type(template.compile('$title$')), + 'pandoc Template' + ) + end), + test('returns a Template', function () + local templ_path = pandoc.path.join{'lua', 'module', 'default.test'} + assert.are_equal( + pandoc.utils.type(template.compile('${ partial() }', templ_path)), + 'pandoc Template' + ) + end), + test('fails if template has non-existing partial', function () + assert.error_matches( + function () return template.compile('${ nosuchpartial() }') end, + 'PandocCouldNotFindDataFileError' + ) + end), + test('works with default template that uses partials', function () + local jats_template = template.default 'jats' + assert.are_equal(type(jats_template), 'string') + assert.are_equal( + pandoc.utils.type(template.compile(jats_template)), + 'pandoc Template' + ) + end), + }, +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-types.lua b/pandoc-lua-engine/test/lua/module/pandoc-types.lua new file mode 100644 index 000000000..d9c9f82ac --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-types.lua @@ -0,0 +1,86 @@ +local tasty = require 'tasty' +local types = require 'pandoc.types' +local Version = types.Version + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'Version' { + + group 'constructor' { + test('has type `userdata`', function () + assert.are_same(type(Version {2}), 'userdata') + end), + test('accepts list of integers', function () + assert.are_same(type(Version {2, 7, 3}), 'userdata') + end), + test('accepts a single integer', function () + assert.are_same(Version(5), Version {5}) + end), + test('accepts version as string', function () + assert.are_same( + Version '4.45.1', + Version {4, 45, 1} + ) + end), + test('non-version string is rejected', function () + local success, msg = pcall(function () Version '11friends' end) + assert.is_falsy(success) + assert.is_truthy(tostring(msg):match('11friends')) + end) + }, + + group 'comparison' { + test('smaller (equal) than', function () + assert.is_truthy(Version {2, 58, 3} < Version {2, 58, 4}) + assert.is_falsy(Version {2, 60, 1} < Version {2, 59, 2}) + assert.is_truthy(Version {0, 14, 3} < Version {0, 14, 3, 1}) + assert.is_truthy(Version {3, 58, 3} <= Version {4}) + assert.is_truthy(Version {0, 14, 3} <= Version {0, 14, 3, 1}) + end), + test('larger (equal) than', function () + assert.is_truthy(Version{2,58,3} > Version {2, 57, 4}) + assert.is_truthy(Version{2,58,3} > Version {2, 58, 2}) + assert.is_truthy(Version {0, 8} >= Version {0, 8}) + assert.is_falsy(Version {0, 8} >= Version {0, 8, 2}) + end), + test('equality', function () + assert.is_truthy(Version '8.8', Version {8, 8}) + end), + test('second argument can be a version string', function () + assert.is_truthy(Version '8' < '9.1') + assert.is_falsy(Version '8.8' < '8.7') + end), + }, + + group 'conversion to string' { + test('converting from and to string is a noop', function () + local version_string = '1.19.4' + assert.are_equal(tostring(Version(version_string)), version_string) + end) + }, + + group 'convenience functions' { + test('throws error if version is too old', function () + local actual = Version {2, 8} + local expected = Version {2, 9} + assert.error_matches( + function () actual:must_be_at_least(expected) end, + 'expected version 2.9 or newer, got 2.8' + ) + end), + test('does nothing if expected version is older than actual', function () + local actual = Version '2.9' + local expected = Version '2.8' + actual:must_be_at_least(expected) + end), + test('does nothing if expected version equals to actual', function () + local actual = Version '2.8' + local expected = Version '2.8' + actual:must_be_at_least(expected) + end) + } + } +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc-utils.lua b/pandoc-lua-engine/test/lua/module/pandoc-utils.lua new file mode 100644 index 000000000..4cf2c84a7 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc-utils.lua @@ -0,0 +1,333 @@ +local tasty = require 'tasty' +local utils = require 'pandoc.utils' + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'blocks_to_inlines' { + test('default separator', function () + local blocks = { + pandoc.Para { pandoc.Str 'Paragraph1' }, + pandoc.Para { pandoc.Emph { pandoc.Str 'Paragraph2' } } + } + local expected = { + pandoc.Str 'Paragraph1', + pandoc.Space(), pandoc.Str '¶', pandoc.Space(), + pandoc.Emph { pandoc.Str 'Paragraph2' } + } + assert.are_same( + expected, + utils.blocks_to_inlines(blocks) + ) + end), + test('custom separator', function () + local blocks = { + pandoc.Para{ pandoc.Str 'Paragraph1' }, + pandoc.Para{ pandoc.Emph 'Paragraph2' } + } + local expected = { + pandoc.Str 'Paragraph1', + pandoc.LineBreak(), + pandoc.Emph { pandoc.Str 'Paragraph2' } + } + assert.are_same( + expected, + utils.blocks_to_inlines(blocks, { pandoc.LineBreak() }) + ) + end) + }, + + group 'equals' { + test('compares Pandoc elements', function () + assert.is_truthy( + utils.equals(pandoc.Pandoc{'foo'}, pandoc.Pandoc{'foo'}) + ) + end), + test('compares Block elements', function () + assert.is_truthy( + utils.equals(pandoc.Plain{'foo'}, pandoc.Plain{'foo'}) + ) + assert.is_falsy( + utils.equals(pandoc.Para{'foo'}, pandoc.Plain{'foo'}) + ) + end), + test('compares Inline elements', function () + assert.is_truthy( + utils.equals(pandoc.Emph{'foo'}, pandoc.Emph{'foo'}) + ) + assert.is_falsy( + utils.equals(pandoc.Emph{'foo'}, pandoc.Strong{'foo'}) + ) + end), + test('compares Inline with Block elements', function () + assert.is_falsy( + utils.equals(pandoc.Emph{'foo'}, pandoc.Plain{'foo'}) + ) + assert.is_falsy( + utils.equals(pandoc.Para{'foo'}, pandoc.Strong{'foo'}) + ) + end), + test('compares Pandoc with Block elements', function () + assert.is_falsy( + utils.equals(pandoc.Pandoc{'foo'}, pandoc.Plain{'foo'}) + ) + assert.is_falsy( + utils.equals(pandoc.Para{'foo'}, pandoc.Pandoc{'foo'}) + ) + end), + }, + + group 'make_sections' { + test('sanity check', function () + local blks = { + pandoc.Header(1, {pandoc.Str 'First'}), + pandoc.Header(2, {pandoc.Str 'Second'}), + pandoc.Header(2, {pandoc.Str 'Third'}), + } + local hblks = utils.make_sections(true, 1, blks) + assert.are_equal('Div', hblks[1].t) + assert.are_equal('Header', hblks[1].content[1].t) + assert.are_equal('1', hblks[1].content[1].attributes['number']) + end) + }, + + group 'normalize_date' { + test('09 Nov 1989', function () + assert.are_equal('1989-11-09', utils.normalize_date '09 Nov 1989') + end), + test('12/31/2017', function () + assert.are_equal('2017-12-31', utils.normalize_date '12/31/2017') + end), + }, + + group 'references' { + test('gets references from doc', function () + local ref = { + ['author'] = { + {given = 'Max', family = 'Mustermann'} + }, + ['container-title'] = pandoc.Inlines('JOSS'), + ['id'] = 'test', + ['issued'] = {['date-parts'] = {{2021}}}, + ['title'] = pandoc.Inlines{ + pandoc.Quoted('DoubleQuote', 'Interesting'), + pandoc.Space(), + 'work' + }, + ['type'] = 'article-journal', + } + local nocite = pandoc.Cite( + '@test', + {pandoc.Citation('test', 'NormalCitation')} + ) + local doc = pandoc.Pandoc({}, {nocite = nocite, references = {ref}}) + assert.are_same({ref}, pandoc.utils.references(doc)) + end) + }, + + group 'sha1' { + test('hashing', function () + local ref_hash = '0a0a9f2a6772942557ab5355d76af442f8f65e01' + assert.are_equal(ref_hash, utils.sha1 'Hello, World!') + end) + }, + + group 'stringify' { + test('Inline', function () + local inline = pandoc.Emph{ + pandoc.Str 'Cogito', + pandoc.Space(), + pandoc.Str 'ergo', + pandoc.Space(), + pandoc.Str 'sum.', + } + assert.are_equal('Cogito ergo sum.', utils.stringify(inline)) + end), + test('Block', function () + local block = pandoc.Para{ + pandoc.Str 'Make', + pandoc.Space(), + pandoc.Str 'it', + pandoc.Space(), + pandoc.Str 'so.', + } + assert.are_equal('Make it so.', utils.stringify(block)) + end), + test('boolean', function () + assert.are_equal('true', utils.stringify(true)) + assert.are_equal('false', utils.stringify(false)) + end), + test('number', function () + assert.are_equal('5', utils.stringify(5)) + assert.are_equal('23.23', utils.stringify(23.23)) + end), + test('Attr', function () + local attr = pandoc.Attr('foo', {'bar'}, {a = 'b'}) + assert.are_equal('', utils.stringify(attr)) + end), + test('List', function () + local list = pandoc.List{pandoc.Str 'a', pandoc.Blocks('b')} + assert.are_equal('ab', utils.stringify(list)) + end), + test('Blocks', function () + local blocks = pandoc.Blocks{pandoc.Para 'a', pandoc.Header(1, 'b')} + assert.are_equal('ab', utils.stringify(blocks)) + end), + test('Inlines', function () + local inlines = pandoc.Inlines{pandoc.Str 'a', pandoc.Subscript('b')} + assert.are_equal('ab', utils.stringify(inlines)) + end), + test('Meta', function () + local meta = pandoc.Meta{ + a = pandoc.Inlines 'funny and ', + b = 'good movie', + c = pandoc.List{pandoc.Inlines{pandoc.Str '!'}} + } + assert.are_equal('funny and good movie!', utils.stringify(meta)) + end), + }, + + group 'to_roman_numeral' { + test('convertes number', function () + assert.are_equal('MDCCCLXXXVIII', utils.to_roman_numeral(1888)) + end), + test('fails on non-convertible argument', function () + assert.is_falsy(pcall(utils.to_roman_numeral, 'not a number')) + end) + }, + + group 'type' { + test('nil', function () + assert.are_equal(utils.type(nil), 'nil') + end), + test('boolean', function () + assert.are_equal(utils.type(true), 'boolean') + assert.are_equal(utils.type(false), 'boolean') + end), + test('number', function () + assert.are_equal(utils.type(5), 'number') + assert.are_equal(utils.type(-3.02), 'number') + end), + test('string', function () + assert.are_equal(utils.type(''), 'string') + assert.are_equal(utils.type('asdf'), 'string') + end), + test('plain table', function () + assert.are_equal(utils.type({}), 'table') + end), + test('List', function () + assert.are_equal(utils.type(pandoc.List{}), 'List') + end), + test('Inline', function () + assert.are_equal(utils.type(pandoc.Str 'a'), 'Inline') + assert.are_equal(utils.type(pandoc.Emph 'emphasized'), 'Inline') + end), + test('Inlines', function () + assert.are_equal(utils.type(pandoc.Inlines{pandoc.Str 'a'}), 'Inlines') + assert.are_equal(utils.type(pandoc.Inlines{pandoc.Emph 'b'}), 'Inlines') + end), + test('Blocks', function () + assert.are_equal(utils.type(pandoc.Para 'a'), 'Block') + assert.are_equal(utils.type(pandoc.CodeBlock 'true'), 'Block') + end), + test('Inlines', function () + assert.are_equal(utils.type(pandoc.Blocks{'a'}), 'Blocks') + assert.are_equal(utils.type(pandoc.Blocks{pandoc.CodeBlock 'b'}), 'Blocks') + end), + }, + + group 'to_simple_table' { + test('convertes Table', function () + function simple_cell (blocks) + return { + attr = pandoc.Attr(), + alignment = "AlignDefault", + contents = blocks, + col_span = 1, + row_span = 1, + } + end + local tbl = pandoc.Table( + {long = {pandoc.Plain { + pandoc.Str "the", pandoc.Space(), pandoc.Str "caption"}}}, + {{pandoc.AlignDefault, nil}}, + pandoc.TableHead{pandoc.Row{simple_cell{pandoc.Plain "head1"}}}, + {{ + attr = pandoc.Attr(), + body = {pandoc.Row{simple_cell{pandoc.Plain "cell1"}}}, + head = {}, + row_head_columns = 0 + }}, + pandoc.TableFoot(), + pandoc.Attr() + ) + local stbl = utils.to_simple_table(tbl) + assert.are_equal('SimpleTable', stbl.t) + assert.are_equal('head1', utils.stringify(stbl.headers[1])) + assert.are_equal('cell1', utils.stringify(stbl.rows[1][1])) + assert.are_equal('the caption', utils.stringify(pandoc.Span(stbl.caption))) + end), + test('fails on para', function () + assert.is_falsy(pcall(utils.to_simple_table, pandoc.Para "nope")) + end), + }, + group 'from_simple_table' { + test('converts SimpleTable to Table', function () + local caption = {pandoc.Str "Overview"} + local aligns = {pandoc.AlignDefault, pandoc.AlignDefault} + local widths = {0, 0} -- let pandoc determine col widths + local headers = { + {pandoc.Plain "Language"}, + {pandoc.Plain "Typing"} + } + local rows = { + {{pandoc.Plain "Haskell"}, {pandoc.Plain "static"}}, + {{pandoc.Plain "Lua"}, {pandoc.Plain "Dynamic"}}, + } + local simple_table = pandoc.SimpleTable( + caption, + aligns, + widths, + headers, + rows + ) + local tbl = utils.from_simple_table(simple_table) + assert.are_equal("Table", tbl.t) + assert.are_same( + {pandoc.Plain(caption)}, + tbl.caption.long + ) + -- reversible + assert.are_same(simple_table, utils.to_simple_table(tbl)) + end), + test('empty caption', function () + local simple_table = pandoc.SimpleTable( + {}, + {pandoc.AlignDefault}, + {0}, + {{pandoc.Plain 'a'}}, + {{{pandoc.Plain 'b'}}} + ) + local tbl = utils.from_simple_table(simple_table) + assert.are_equal( + pandoc.Blocks{}, + tbl.caption.long + ) + assert.is_nil(tbl.caption.short) + end), + test('empty body', function () + local simple_table = pandoc.SimpleTable( + pandoc.Inlines('a nice caption'), + {pandoc.AlignDefault}, + {0}, + {{pandoc.Plain 'a'}}, + {} + ) + local tbl = utils.from_simple_table(simple_table) + tbl.bodies:map(print) + assert.are_same(pandoc.List(), tbl.bodies) + end), + } +} diff --git a/pandoc-lua-engine/test/lua/module/pandoc.lua b/pandoc-lua-engine/test/lua/module/pandoc.lua new file mode 100644 index 000000000..397182438 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/pandoc.lua @@ -0,0 +1,356 @@ +local tasty = require 'tasty' + +local test = tasty.test_case +local group = tasty.test_group +local assert = tasty.assert + +function os_is_windows () + return package.config:sub(1,1) == '\\' +end + +-- Constructor behavior is tested in the hslua-pandoc-types module, so +-- we just make sure the functions are present. +return { + group 'Constructors' { + group 'Misc' { + test('pandoc.Attr is a function', function () + assert.are_equal(type(pandoc.Attr), 'function') + end), + test('pandoc.AttributeList is a function', function () + assert.are_equal(type(pandoc.AttributeList), 'function') + end), + test('pandoc.Blocks is a function', function () + assert.are_equal(type(pandoc.Blocks), 'function') + end), + test('pandoc.Citation is a function', function () + assert.are_equal(type(pandoc.Citation), 'function') + end), + test('pandoc.Inlines is a function', function () + assert.are_equal(type(pandoc.Inlines), 'function') + end), + test('pandoc.SimpleTable is a function', function () + assert.are_equal(type(pandoc.SimpleTable), 'function') + end), + test('pandoc.Meta is a function', function () + assert.are_equal(type(pandoc.Meta), 'function') + end), + test('pandoc.Pandoc is a function', function () + assert.are_equal(type(pandoc.Pandoc), 'function') + end), + }, + group "Inline elements" { + test('pandoc.AttributeList is a function', function () + assert.are_equal(type(pandoc.Cite), 'function') + end), + test('pandoc.AttributeList is a function', function () + assert.are_equal(type(pandoc.Code), 'function') + end), + test('pandoc.Emph is a function', function () + assert.are_equal(type(pandoc.Emph), 'function') + end), + test('pandoc.Image is a function', function () + assert.are_equal(type(pandoc.Image), 'function') + end), + test('pandoc.Link is a function', function () + assert.are_equal(type(pandoc.Link), 'function') + end), + test('pandoc.Math is a function', function () + assert.are_equal(type(pandoc.Math), 'function') + end), + test('pandoc.Note is a function', function () + assert.are_equal(type(pandoc.Note), 'function') + end), + test('pandoc.Quoted is a function', function () + assert.are_equal(type(pandoc.Quoted), 'function') + end), + test('pandoc.SmallCaps is a function', function () + assert.are_equal(type(pandoc.SmallCaps), 'function') + end), + test('pandoc.SoftBreak is a function', function () + assert.are_equal(type(pandoc.SoftBreak), 'function') + end), + test('pandoc.Span is a function', function () + assert.are_equal(type(pandoc.Span), 'function') + end), + test('pandoc.Str is a function', function () + assert.are_equal(type(pandoc.Str), 'function') + end), + test('pandoc.Strikeout is a function', function () + assert.are_equal(type(pandoc.Strikeout), 'function') + end), + test('pandoc.Strong is a function', function () + assert.are_equal(type(pandoc.Strong), 'function') + end), + test('pandoc.Subscript is a function', function () + assert.are_equal(type(pandoc.Subscript), 'function') + end), + test('pandoc.Superscript is a function', function () + assert.are_equal(type(pandoc.Superscript), 'function') + end), + test('pandoc.Underline is a function', function () + assert.are_equal(type(pandoc.Underline), 'function') + end), + }, + group "Block elements" { + test('pandoc.BlockQuote is a function', function () + assert.are_equal(type(pandoc.BlockQuote), 'function') + end), + test('pandoc.BulletList is a function', function () + assert.are_equal(type(pandoc.BulletList), 'function') + end), + test('pandoc.CodeBlock is a function', function () + assert.are_equal(type(pandoc.CodeBlock), 'function') + end), + test('pandoc.DefinitionList is a function', function () + assert.are_equal(type(pandoc.DefinitionList), 'function') + end), + test('pandoc.Div is a function', function () + assert.are_equal(type(pandoc.Div), 'function') + end), + test('pandoc.Header is a function', function () + assert.are_equal(type(pandoc.Header), 'function') + end), + test('pandoc.LineBlock is a function', function () + assert.are_equal(type(pandoc.LineBlock), 'function') + end), + test('pandoc.Null is a function', function () + assert.are_equal(type(pandoc.Null), 'function') + end), + test('pandoc.OrderedList is a function', function () + assert.are_equal(type(pandoc.OrderedList), 'function') + end), + test('pandoc.Para is a function', function () + assert.are_equal(type(pandoc.Para), 'function') + end), + test('pandoc.Plain is a function', function () + assert.are_equal(type(pandoc.Plain), 'function') + end), + test('pandoc.RawBlock is a function', function () + assert.are_equal(type(pandoc.Plain), 'function') + end), + test('pandoc.Table is a function', function () + assert.are_equal(type(pandoc.Table), 'function') + end), + } + }, + group 'MetaValue elements' { + test('MetaList elements behave like lists', function () + local metalist = pandoc.MetaList{} + assert.are_equal(type(metalist.insert), 'function') + assert.are_equal(type(metalist.remove), 'function') + end), + test('`tag` is an alias for `t``', function () + assert.are_equal((pandoc.MetaList{}).tag, (pandoc.MetaList{}).t) + assert.are_equal((pandoc.MetaMap{}).tag, (pandoc.MetaMap{}).t) + assert.are_equal((pandoc.MetaInlines{}).tag, (pandoc.MetaInlines{}).t) + assert.are_equal((pandoc.MetaBlocks{}).tag, (pandoc.MetaBlocks{}).t) + end), + }, + group 'Meta' { + test('inline list is treated as MetaInlines', function () + local meta = pandoc.Pandoc({}, {test = {pandoc.Emph 'check'}}).meta + assert.are_same(meta.test, {pandoc.Emph{pandoc.Str 'check'}}) + end), + test('inline element is treated as MetaInlines singleton', function () + local meta = pandoc.Pandoc({}, {test = pandoc.Emph 'check'}).meta + assert.are_same(meta.test, {pandoc.Emph{pandoc.Str 'check'}}) + end), + test('block list is treated as MetaBlocks', function () + local meta = pandoc.Pandoc({}, {test = {pandoc.Plain 'check'}}).meta + assert.are_same(meta.test, {pandoc.Plain{pandoc.Str 'check'}}) + end), + test('block element is treated as MetaBlocks singleton', function () + local meta = pandoc.Pandoc({}, {test = pandoc.Plain 'check'}).meta + assert.are_same(meta.test, {pandoc.Plain{pandoc.Str 'check'}}) + end), + }, + group 'Other types' { + group 'ReaderOptions' { + test('returns a userdata value', function () + local opts = pandoc.ReaderOptions {} + assert.are_equal(type(opts), 'userdata') + end), + test('can construct from table', function () + local opts = pandoc.ReaderOptions {columns = 66} + assert.are_equal(opts.columns, 66) + end), + test('can construct from other ReaderOptions value', function () + local orig = pandoc.ReaderOptions{columns = 65} + local copy = pandoc.ReaderOptions(orig) + for k, v in pairs(orig) do + assert.are_same(copy[k], v) + end + assert.are_equal(copy.columns, 65) + end), + }, + }, + + group 'clone' { + test('clones Attr', function () + local attr = pandoc.Attr('test', {'my-class'}, {foo = 'bar'}) + local cloned = attr:clone() + attr.identifier = '' + attr.classes = {} + attr.attributes = {} + assert.are_same(cloned.identifier, 'test') + assert.are_same(cloned.classes, {'my-class'}) + assert.are_same(cloned.attributes.foo, 'bar') + end), + test('clones ListAttributes', function () + local la = pandoc.ListAttributes(2, pandoc.DefaultStyle, pandoc.Period) + local cloned = la:clone() + la.start = 9 + assert.are_same(cloned.start, 2) + end), + test('clones Para', function () + local para = pandoc.Para {pandoc.Str 'Hello'} + local cloned = para:clone() + para.content[1].text = 'bye' + assert.are_same(cloned, pandoc.Para {pandoc.Str 'Hello'}) + end), + test('clones Str', function () + local str = pandoc.Str 'Hello' + local cloned = str:clone() + str.text = 'bye' + assert.are_same(cloned.text, 'Hello') + end), + test('clones Citation', function () + local cite = pandoc.Citation('leibniz', pandoc.AuthorInText) + local cloned = cite:clone() + cite.id = 'newton' + assert.are_same(cloned.id, 'leibniz') + assert.are_same(cite.id, 'newton') + assert.are_same(cite.mode, cloned.mode) + end), + }, + + group 'pipe' { + test('external string processing', function () + if os_is_windows() then + local pipe_result = pandoc.pipe('find', {'hi'}, 'hi') + assert.are_equal('hi', pipe_result:match '%a+') + else + local pipe_result = pandoc.pipe('tr', {'a', 'b'}, 'abc') + assert.are_equal('bbc', pipe_result:match '%a+') + end + end), + test('failing pipe', function () + if os_is_windows() then + local success, err = pcall(pandoc.pipe, 'find', {'/a'}, 'hi') + assert.is_falsy(success) + assert.are_equal('find', err.command) + assert.is_truthy(err.error_code ~= 0) + else + local success, err = pcall(pandoc.pipe, 'false', {}, 'abc') + assert.is_falsy(success) + assert.are_equal('false', err.command) + assert.are_equal(1, err.error_code) + assert.are_equal('', err.output) + end + end) + }, + + group 'read' { + test('Markdown', function () + local valid_markdown = '*Hello*, World!\n' + local expected = pandoc.Pandoc({ + pandoc.Para { + pandoc.Emph { pandoc.Str 'Hello' }, + pandoc.Str ',', + pandoc.Space(), + pandoc.Str 'World!' + } + }) + assert.are_same(expected, pandoc.read(valid_markdown)) + end), + test('unsupported extension', function () + assert.error_matches( + function () pandoc.read('foo', 'gfm+empty_paragraphs') end, + 'Extension empty_paragraphs not supported for gfm' + ) + end), + test('read with other indented code classes', function() + local indented_code = ' return true' + local expected = pandoc.Pandoc({ + pandoc.CodeBlock('return true', {class='foo'}) + }) + assert.are_same( + expected, + pandoc.read(indented_code, 'markdown', {indented_code_classes={'foo'}}) + ) + end), + test('can read epub', function () + local epub = io.open('lua/module/tiny.epub', 'rb') + local blocks = pandoc.read(epub:read'a', 'epub').blocks + assert.are_equal( + blocks[#blocks], + pandoc.Para { pandoc.Emph 'EPUB' } + ) + end), + test('failing read', function () + assert.error_matches( + function () pandoc.read('foo', 'nosuchreader') end, + 'Unknown reader: nosuchreader' + ) + end) + }, + + group 'walk_block' { + test('block walking order', function () + local acc = {} + local nested_nums = pandoc.Div { + pandoc.Para{pandoc.Str'1'}, + pandoc.Div{ + pandoc.Para{pandoc.Str'2'}, + pandoc.Para{pandoc.Str'3'} + }, + pandoc.Para{pandoc.Str'4'} + } + pandoc.walk_block( + nested_nums, + {Para = function (p) table.insert(acc, p.content[1].text) end} + ) + assert.are_equal('1234', table.concat(acc)) + end) + }, + + group 'walk_inline' { + test('inline walking order', function () + local acc = {} + local nested_nums = pandoc.Span { + pandoc.Str'1', + pandoc.Emph { + pandoc.Str'2', + pandoc.Str'3' + }, + pandoc.Str'4' + } + pandoc.walk_inline( + nested_nums, + {Str = function (s) table.insert(acc, s.text) end} + ) + assert.are_equal('1234', table.concat(acc)) + end) + }, + + group 'Marshal' { + group 'Inlines' { + test('Strings are broken into words', function () + assert.are_equal( + pandoc.Emph 'Nice, init?', + pandoc.Emph{pandoc.Str 'Nice,', pandoc.Space(), pandoc.Str 'init?'} + ) + end) + }, + group 'Blocks' { + test('Strings are broken into words and wrapped in Plain', function () + assert.are_equal( + pandoc.Div{ + pandoc.Plain{pandoc.Str 'Nice,', pandoc.Space(), pandoc.Str 'init?'} + }, + pandoc.Div{'Nice, init?'} + ) + end) + } + } +} diff --git a/pandoc-lua-engine/test/lua/module/partial.test b/pandoc-lua-engine/test/lua/module/partial.test new file mode 100644 index 000000000..e69de29bb --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/partial.test diff --git a/pandoc-lua-engine/test/lua/module/tiny.epub b/pandoc-lua-engine/test/lua/module/tiny.epub Binary files differnew file mode 100644 index 000000000..9e92202b7 --- /dev/null +++ b/pandoc-lua-engine/test/lua/module/tiny.epub diff --git a/pandoc-lua-engine/test/lua/plain-to-para.lua b/pandoc-lua-engine/test/lua/plain-to-para.lua new file mode 100644 index 000000000..aa12a97d3 --- /dev/null +++ b/pandoc-lua-engine/test/lua/plain-to-para.lua @@ -0,0 +1,6 @@ +return { + { Plain = function (elem) + return pandoc.Para(elem.content) + end, + } +} diff --git a/pandoc-lua-engine/test/lua/require-file.lua b/pandoc-lua-engine/test/lua/require-file.lua new file mode 100644 index 000000000..d610e5266 --- /dev/null +++ b/pandoc-lua-engine/test/lua/require-file.lua @@ -0,0 +1,2 @@ +package.path = package.path .. ';lua/?.lua' +require 'script-name' diff --git a/pandoc-lua-engine/test/lua/script-name.lua b/pandoc-lua-engine/test/lua/script-name.lua new file mode 100644 index 000000000..4b5a223f0 --- /dev/null +++ b/pandoc-lua-engine/test/lua/script-name.lua @@ -0,0 +1,3 @@ +function Para (_) + return pandoc.Para{pandoc.Str(PANDOC_SCRIPT_FILE)} +end diff --git a/pandoc-lua-engine/test/lua/single-to-double-quoted.lua b/pandoc-lua-engine/test/lua/single-to-double-quoted.lua new file mode 100644 index 000000000..b985b215c --- /dev/null +++ b/pandoc-lua-engine/test/lua/single-to-double-quoted.lua @@ -0,0 +1,10 @@ +return { + { + Quoted = function (elem) + if elem.quotetype == "SingleQuote" then + elem.quotetype = "DoubleQuote" + end + return elem + end, + } +} diff --git a/pandoc-lua-engine/test/lua/smallcaps-title.lua b/pandoc-lua-engine/test/lua/smallcaps-title.lua new file mode 100644 index 000000000..b839ee131 --- /dev/null +++ b/pandoc-lua-engine/test/lua/smallcaps-title.lua @@ -0,0 +1,12 @@ +return { + { + Meta = function(meta) + -- The call to `MetaInlines` is redundant and used for testing purposes + -- only. The explicit use of a MetaValue constructor is only useful when + -- used with an empty table: `MetaInlines{}` is read differently than + -- `MetaBlocks{}`. + meta.title = pandoc.MetaInlines{pandoc.SmallCaps(meta.title)} + return meta + end + } +} diff --git a/pandoc-lua-engine/test/lua/smart-constructors.lua b/pandoc-lua-engine/test/lua/smart-constructors.lua new file mode 100644 index 000000000..6e579a12f --- /dev/null +++ b/pandoc-lua-engine/test/lua/smart-constructors.lua @@ -0,0 +1,10 @@ +-- Test that constructors are "smart" in that they autoconvert +-- types where sensible. +function Para (_) + return { + pandoc.BulletList{pandoc.Para "Hello", pandoc.Para "World"}, + pandoc.DefinitionList{{"foo", pandoc.Para "placeholder"}}, + pandoc.LineBlock{"Moin", "Welt"}, + pandoc.OrderedList{pandoc.Plain{pandoc.Str "one"}, pandoc.Plain "two"} + } +end diff --git a/pandoc-lua-engine/test/lua/strmacro.lua b/pandoc-lua-engine/test/lua/strmacro.lua new file mode 100644 index 000000000..a2711798a --- /dev/null +++ b/pandoc-lua-engine/test/lua/strmacro.lua @@ -0,0 +1,11 @@ +return { + { + Str = function (elem) + if elem.text == "{{helloworld}}" then + return pandoc.Emph {pandoc.Str "Hello, World"} + else + return elem + end + end, + } +} diff --git a/pandoc-lua-engine/test/lua/undiv.lua b/pandoc-lua-engine/test/lua/undiv.lua new file mode 100644 index 000000000..1cbb6d30e --- /dev/null +++ b/pandoc-lua-engine/test/lua/undiv.lua @@ -0,0 +1,3 @@ +function Div(el) + return el.content +end diff --git a/pandoc-lua-engine/test/lua/uppercase-header.lua b/pandoc-lua-engine/test/lua/uppercase-header.lua new file mode 100644 index 000000000..8e86911c0 --- /dev/null +++ b/pandoc-lua-engine/test/lua/uppercase-header.lua @@ -0,0 +1,9 @@ +local text = require 'text' + +local function str_to_uppercase (s) + return pandoc.Str(text.upper(s.text)) +end + +function Header (el) + return pandoc.walk_block(el, {Str = str_to_uppercase}) +end diff --git a/pandoc-lua-engine/test/sample.lua b/pandoc-lua-engine/test/sample.lua new file mode 120000 index 000000000..b2f5a1a10 --- /dev/null +++ b/pandoc-lua-engine/test/sample.lua @@ -0,0 +1 @@ +../../data/sample.lua
\ No newline at end of file diff --git a/pandoc-lua-engine/test/tables.custom b/pandoc-lua-engine/test/tables.custom new file mode 100644 index 000000000..ce0268edf --- /dev/null +++ b/pandoc-lua-engine/test/tables.custom @@ -0,0 +1,200 @@ +<p>Simple table with caption:</p> + +<table> +<caption>Demonstration of simple table syntax.</caption> +<tr class="header"> +<th align="right">Right</th> +<th align="left">Left</th> +<th align="center">Center</th> +<th align="left">Default</th> +</tr> +<tr class="odd"> +<td align="right">12</td> +<td align="left">12</td> +<td align="center">12</td> +<td align="left">12</td> +</tr> +<tr class="even"> +<td align="right">123</td> +<td align="left">123</td> +<td align="center">123</td> +<td align="left">123</td> +</tr> +<tr class="odd"> +<td align="right">1</td> +<td align="left">1</td> +<td align="center">1</td> +<td align="left">1</td> +</tr> +</table> + +<p>Simple table without caption:</p> + +<table> +<tr class="header"> +<th align="right">Right</th> +<th align="left">Left</th> +<th align="center">Center</th> +<th align="left">Default</th> +</tr> +<tr class="odd"> +<td align="right">12</td> +<td align="left">12</td> +<td align="center">12</td> +<td align="left">12</td> +</tr> +<tr class="even"> +<td align="right">123</td> +<td align="left">123</td> +<td align="center">123</td> +<td align="left">123</td> +</tr> +<tr class="odd"> +<td align="right">1</td> +<td align="left">1</td> +<td align="center">1</td> +<td align="left">1</td> +</tr> +</table> + +<p>Simple table indented two spaces:</p> + +<table> +<caption>Demonstration of simple table syntax.</caption> +<tr class="header"> +<th align="right">Right</th> +<th align="left">Left</th> +<th align="center">Center</th> +<th align="left">Default</th> +</tr> +<tr class="odd"> +<td align="right">12</td> +<td align="left">12</td> +<td align="center">12</td> +<td align="left">12</td> +</tr> +<tr class="even"> +<td align="right">123</td> +<td align="left">123</td> +<td align="center">123</td> +<td align="left">123</td> +</tr> +<tr class="odd"> +<td align="right">1</td> +<td align="left">1</td> +<td align="center">1</td> +<td align="left">1</td> +</tr> +</table> + +<p>Multiline table with caption:</p> + +<table> +<caption>Here’s the caption. +It may span multiple lines.</caption> +<col width="15%" /> +<col width="14%" /> +<col width="16%" /> +<col width="35%" /> +<tr class="header"> +<th align="center">Centered +Header</th> +<th align="left">Left +Aligned</th> +<th align="right">Right +Aligned</th> +<th align="left">Default aligned</th> +</tr> +<tr class="odd"> +<td align="center">First</td> +<td align="left">row</td> +<td align="right">12.0</td> +<td align="left">Example of a row that spans +multiple lines.</td> +</tr> +<tr class="even"> +<td align="center">Second</td> +<td align="left">row</td> +<td align="right">5.0</td> +<td align="left">Here’s another one. Note +the blank line between rows.</td> +</tr> +</table> + +<p>Multiline table without caption:</p> + +<table> +<col width="15%" /> +<col width="14%" /> +<col width="16%" /> +<col width="35%" /> +<tr class="header"> +<th align="center">Centered +Header</th> +<th align="left">Left +Aligned</th> +<th align="right">Right +Aligned</th> +<th align="left">Default aligned</th> +</tr> +<tr class="odd"> +<td align="center">First</td> +<td align="left">row</td> +<td align="right">12.0</td> +<td align="left">Example of a row that spans +multiple lines.</td> +</tr> +<tr class="even"> +<td align="center">Second</td> +<td align="left">row</td> +<td align="right">5.0</td> +<td align="left">Here’s another one. Note +the blank line between rows.</td> +</tr> +</table> + +<p>Table without column headers:</p> + +<table> +<tr class="odd"> +<td align="right">12</td> +<td align="left">12</td> +<td align="center">12</td> +<td align="right">12</td> +</tr> +<tr class="even"> +<td align="right">123</td> +<td align="left">123</td> +<td align="center">123</td> +<td align="right">123</td> +</tr> +<tr class="odd"> +<td align="right">1</td> +<td align="left">1</td> +<td align="center">1</td> +<td align="right">1</td> +</tr> +</table> + +<p>Multiline table without column headers:</p> + +<table> +<col width="15%" /> +<col width="14%" /> +<col width="16%" /> +<col width="35%" /> +<tr class="odd"> +<td align="center">First</td> +<td align="left">row</td> +<td align="right">12.0</td> +<td align="left">Example of a row that spans +multiple lines.</td> +</tr> +<tr class="even"> +<td align="center">Second</td> +<td align="left">row</td> +<td align="right">5.0</td> +<td align="left">Here’s another one. Note +the blank line between rows.</td> +</tr> +</table> diff --git a/pandoc-lua-engine/test/tables.native b/pandoc-lua-engine/test/tables.native new file mode 120000 index 000000000..b2585393d --- /dev/null +++ b/pandoc-lua-engine/test/tables.native @@ -0,0 +1 @@ +../../test/tables.native
\ No newline at end of file diff --git a/pandoc-lua-engine/test/test-pandoc-lua-engine.hs b/pandoc-lua-engine/test/test-pandoc-lua-engine.hs new file mode 100644 index 000000000..035d92812 --- /dev/null +++ b/pandoc-lua-engine/test/test-pandoc-lua-engine.hs @@ -0,0 +1,16 @@ +module Main (main) where +import Test.Tasty (TestTree, defaultMain, testGroup) +import qualified Tests.Lua +import qualified Tests.Lua.Module +import qualified Tests.Lua.Writer +import System.Directory (withCurrentDirectory) + +main :: IO () +main = withCurrentDirectory "test" $ defaultMain tests + +tests :: TestTree +tests = testGroup "pandoc Lua engine" + [ testGroup "Lua filters" Tests.Lua.tests + , testGroup "Lua modules" Tests.Lua.Module.tests + , testGroup "Custom writers" Tests.Lua.Writer.tests + ] diff --git a/pandoc-lua-engine/test/testsuite.native b/pandoc-lua-engine/test/testsuite.native new file mode 120000 index 000000000..7f0fd1f26 --- /dev/null +++ b/pandoc-lua-engine/test/testsuite.native @@ -0,0 +1 @@ +../../test/testsuite.native
\ No newline at end of file diff --git a/pandoc-lua-engine/test/writer.custom b/pandoc-lua-engine/test/writer.custom new file mode 100644 index 000000000..eb53363fa --- /dev/null +++ b/pandoc-lua-engine/test/writer.custom @@ -0,0 +1,781 @@ +<p>This is a set of tests for pandoc. Most of them are adapted from +John Gruber’s markdown test suite.</p> + +<hr/> + +<h1 id="headers">Headers</h1> + +<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url" title="">embedded link</a></h2> + +<h3 id="level-3-with-emphasis">Level 3 with <em>emphasis</em></h3> + +<h4 id="level-4">Level 4</h4> + +<h5 id="level-5">Level 5</h5> + +<h1 id="level-1">Level 1</h1> + +<h2 id="level-2-with-emphasis">Level 2 with <em>emphasis</em></h2> + +<h3 id="level-3">Level 3</h3> + +<p>with no blank line</p> + +<h2 id="level-2">Level 2</h2> + +<p>with no blank line</p> + +<hr/> + +<h1 id="paragraphs">Paragraphs</h1> + +<p>Here’s a regular paragraph.</p> + +<p>In Markdown 1.0.0 and earlier. Version +8. This line turns into a list item. +Because a hard-wrapped line in the +middle of a paragraph looked like a +list item.</p> + +<p>Here’s one with a bullet. +* criminey.</p> + +<p>There should be a hard line break<br/>here.</p> + +<hr/> + +<h1 id="block-quotes">Block Quotes</h1> + +<p>E-mail style:</p> + +<blockquote> +<p>This is a block quote. +It is pretty short.</p> +</blockquote> + +<blockquote> +<p>Code in a block quote:</p> + +<pre><code>sub status { + print "working"; +}</code></pre> + +<p>A list:</p> + +<ol> +<li>item one</li> +<li>item two</li> +</ol> + +<p>Nested block quotes:</p> + +<blockquote> +<p>nested</p> +</blockquote> + +<blockquote> +<p>nested</p> +</blockquote> +</blockquote> + +<p>This should not be a block quote: 2 +> 1.</p> + +<p>And a following paragraph.</p> + +<hr/> + +<h1 id="code-blocks">Code Blocks</h1> + +<p>Code:</p> + +<pre><code>---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab</code></pre> + +<p>And:</p> + +<pre><code> this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{</code></pre> + +<hr/> + +<h1 id="lists">Lists</h1> + +<h2 id="unordered">Unordered</h2> + +<p>Asterisks tight:</p> + +<ul> +<li>asterisk 1</li> +<li>asterisk 2</li> +<li>asterisk 3</li> +</ul> + +<p>Asterisks loose:</p> + +<ul> +<li><p>asterisk 1</p></li> +<li><p>asterisk 2</p></li> +<li><p>asterisk 3</p></li> +</ul> + +<p>Pluses tight:</p> + +<ul> +<li>Plus 1</li> +<li>Plus 2</li> +<li>Plus 3</li> +</ul> + +<p>Pluses loose:</p> + +<ul> +<li><p>Plus 1</p></li> +<li><p>Plus 2</p></li> +<li><p>Plus 3</p></li> +</ul> + +<p>Minuses tight:</p> + +<ul> +<li>Minus 1</li> +<li>Minus 2</li> +<li>Minus 3</li> +</ul> + +<p>Minuses loose:</p> + +<ul> +<li><p>Minus 1</p></li> +<li><p>Minus 2</p></li> +<li><p>Minus 3</p></li> +</ul> + +<h2 id="ordered">Ordered</h2> + +<p>Tight:</p> + +<ol> +<li>First</li> +<li>Second</li> +<li>Third</li> +</ol> + +<p>and:</p> + +<ol> +<li>One</li> +<li>Two</li> +<li>Three</li> +</ol> + +<p>Loose using tabs:</p> + +<ol> +<li><p>First</p></li> +<li><p>Second</p></li> +<li><p>Third</p></li> +</ol> + +<p>and using spaces:</p> + +<ol> +<li><p>One</p></li> +<li><p>Two</p></li> +<li><p>Three</p></li> +</ol> + +<p>Multiple paragraphs:</p> + +<ol> +<li><p>Item 1, graf one.</p> + +<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s +back.</p></li> +<li><p>Item 2.</p></li> +<li><p>Item 3.</p></li> +</ol> + +<h2 id="nested">Nested</h2> + +<ul> +<li>Tab + +<ul> +<li>Tab + +<ul> +<li>Tab</li> +</ul></li> +</ul></li> +</ul> + +<p>Here’s another:</p> + +<ol> +<li>First</li> +<li>Second: + +<ul> +<li>Fee</li> +<li>Fie</li> +<li>Foe</li> +</ul></li> +<li>Third</li> +</ol> + +<p>Same thing but with paragraphs:</p> + +<ol> +<li><p>First</p></li> +<li><p>Second:</p> + +<ul> +<li>Fee</li> +<li>Fie</li> +<li>Foe</li> +</ul></li> +<li><p>Third</p></li> +</ol> + +<h2 id="tabs-and-spaces">Tabs and spaces</h2> + +<ul> +<li><p>this is a list item +indented with tabs</p></li> +<li><p>this is a list item +indented with spaces</p> + +<ul> +<li><p>this is an example list item +indented with tabs</p></li> +<li><p>this is an example list item +indented with spaces</p></li> +</ul></li> +</ul> + +<h2 id="fancy-list-markers">Fancy list markers</h2> + +<ol> +<li><p>begins with 2</p></li> +<li><p>and now 3</p> + +<p>with a continuation</p> + +<ol> +<li>sublist with roman numerals, +starting with 4</li> +<li>more items + +<ol> +<li>a subsublist</li> +<li>a subsublist</li> +</ol></li> +</ol></li> +</ol> + +<p>Nesting:</p> + +<ol> +<li>Upper Alpha + +<ol> +<li>Upper Roman. + +<ol> +<li>Decimal start with 6 + +<ol> +<li>Lower alpha with paren</li> +</ol></li> +</ol></li> +</ol></li> +</ol> + +<p>Autonumbering:</p> + +<ol> +<li>Autonumber.</li> +<li>More. + +<ol> +<li>Nested.</li> +</ol></li> +</ol> + +<p>Should not be a list item:</p> + +<p>M.A. 2007</p> + +<p>B. Williams</p> + +<hr/> + +<h1 id="definition-lists">Definition Lists</h1> + +<p>Tight using spaces:</p> + +<dl> +<dt>apple</dt> +<dd>red fruit</dd> +<dt>orange</dt> +<dd>orange fruit</dd> +<dt>banana</dt> +<dd>yellow fruit</dd> +</dl> + +<p>Tight using tabs:</p> + +<dl> +<dt>apple</dt> +<dd>red fruit</dd> +<dt>orange</dt> +<dd>orange fruit</dd> +<dt>banana</dt> +<dd>yellow fruit</dd> +</dl> + +<p>Loose:</p> + +<dl> +<dt>apple</dt> +<dd><p>red fruit</p></dd> +<dt>orange</dt> +<dd><p>orange fruit</p></dd> +<dt>banana</dt> +<dd><p>yellow fruit</p></dd> +</dl> + +<p>Multiple blocks with italics:</p> + +<dl> +<dt><em>apple</em></dt> +<dd><p>red fruit</p> + +<p>contains seeds, +crisp, pleasant to taste</p></dd> +<dt><em>orange</em></dt> +<dd><p>orange fruit</p> + +<pre><code>{ orange code block }</code></pre> + +<blockquote> +<p>orange block quote</p> +</blockquote></dd> +</dl> + +<p>Multiple definitions, tight:</p> + +<dl> +<dt>apple</dt> +<dd>red fruit</dd> +<dd>computer</dd> +<dt>orange</dt> +<dd>orange fruit</dd> +<dd>bank</dd> +</dl> + +<p>Multiple definitions, loose:</p> + +<dl> +<dt>apple</dt> +<dd><p>red fruit</p></dd> +<dd><p>computer</p></dd> +<dt>orange</dt> +<dd><p>orange fruit</p></dd> +<dd><p>bank</p></dd> +</dl> + +<p>Blank line after term, indented marker, alternate markers:</p> + +<dl> +<dt>apple</dt> +<dd><p>red fruit</p></dd> +<dd><p>computer</p></dd> +<dt>orange</dt> +<dd><p>orange fruit</p> + +<ol> +<li>sublist</li> +<li>sublist</li> +</ol></dd> +</dl> + +<h1 id="html-blocks">HTML Blocks</h1> + +<p>Simple block on one line:</p> + +<div> +foo</div> + +<p>And nested without indentation:</p> + +<div> +<div> +<div> +<p>foo</p></div></div> + +<div> +bar</div></div> + +<p>Interpreted markdown in a table:</p> + +<table> + +<tr> + +<td> + +This is <em>emphasized</em> + +</td> + +<td> + +And this is <strong>strong</strong> + +</td> + +</tr> + +</table> + +<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> + +<p>Here’s a simple block:</p> + +<div> +<p>foo</p></div> + +<p>This should be a code block, though:</p> + +<pre><code><div> + foo +</div></code></pre> + +<p>As should this:</p> + +<pre><code><div>foo</div></code></pre> + +<p>Now, nested:</p> + +<div> +<div> +<div> +foo</div></div></div> + +<p>This should just be an HTML comment:</p> + +<!-- Comment --> + +<p>Multiline:</p> + +<!-- +Blah +Blah +--> + +<!-- + This is another comment. +--> + +<p>Code block:</p> + +<pre><code><!-- Comment --></code></pre> + +<p>Just plain comment, with trailing spaces on the line:</p> + +<!-- foo --> + +<p>Code:</p> + +<pre><code><hr /></code></pre> + +<p>Hr’s:</p> + +<hr> + +<hr /> + +<hr /> + +<hr> + +<hr /> + +<hr /> + +<hr class="foo" id="bar" /> + +<hr class="foo" id="bar" /> + +<hr class="foo" id="bar"> + +<hr/> + +<h1 id="inline-markup">Inline Markup</h1> + +<p>This is <em>emphasized</em>, and so <em>is this</em>.</p> + +<p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p> + +<p>An <em><a href="/url" title="">emphasized link</a></em>.</p> + +<p><strong><em>This is strong and em.</em></strong></p> + +<p>So is <strong><em>this</em></strong> word.</p> + +<p><strong><em>This is strong and em.</em></strong></p> + +<p>So is <strong><em>this</em></strong> word.</p> + +<p>This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code><html></code>.</p> + +<p><del>This is <em>strikeout</em>.</del></p> + +<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup> a<sup>hello there</sup>.</p> + +<p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.</p> + +<p>These should not be superscripts or subscripts, +because of the unescaped spaces: a^b c^d, a~b c~d.</p> + +<hr/> + +<h1 id="smart-quotes-ellipses-dashes">Smart quotes, ellipses, dashes</h1> + +<p>“Hello,” said the spider. “‘Shelob’ is my name.”</p> + +<p>‘A’, ‘B’, and ‘C’ are letters.</p> + +<p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. +So is ‘pine.’</p> + +<p>‘He said, “I want to go.”’ Were you alive in the +70’s?</p> + +<p>Here is some quoted ‘<code>code</code>’ and a “<a href="http://example.com/?foo=1&bar=2" title="">quoted link</a>”.</p> + +<p>Some dashes: one—two — three—four — five.</p> + +<p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p> + +<p>Ellipses…and…and….</p> + +<hr/> + +<h1 id="latex">LaTeX</h1> + +<ul> +<li></li> +<li>\(2+2=4\)</li> +<li>\(x \in y\)</li> +<li>\(\alpha \wedge \omega\)</li> +<li>\(223\)</li> +<li>\(p\)-Tree</li> +<li>Here’s some display math: +\[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\]</li> +<li>Here’s one that has a line break in it: \(\alpha + \omega \times x^2\).</li> +</ul> + +<p>These shouldn’t be math:</p> + +<ul> +<li>To get the famous equation, write <code>$e = mc^2$</code>.</li> +<li>$22,000 is a <em>lot</em> of money. So is $34,000. +(It worked if “lot” is emphasized.)</li> +<li>Shoes ($20) and socks ($5).</li> +<li>Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.</li> +</ul> + +<p>Here’s a LaTeX table:</p> + + + +<hr/> + +<h1 id="special-characters">Special Characters</h1> + +<p>Here is some unicode:</p> + +<ul> +<li>I hat: Î</li> +<li>o umlaut: ö</li> +<li>section: §</li> +<li>set membership: ∈</li> +<li>copyright: ©</li> +</ul> + +<p>AT&T has an ampersand in their name.</p> + +<p>AT&T is another way to write it.</p> + +<p>This & that.</p> + +<p>4 < 5.</p> + +<p>6 > 5.</p> + +<p>Backslash: \</p> + +<p>Backtick: `</p> + +<p>Asterisk: *</p> + +<p>Underscore: _</p> + +<p>Left brace: {</p> + +<p>Right brace: }</p> + +<p>Left bracket: [</p> + +<p>Right bracket: ]</p> + +<p>Left paren: (</p> + +<p>Right paren: )</p> + +<p>Greater-than: ></p> + +<p>Hash: #</p> + +<p>Period: .</p> + +<p>Bang: !</p> + +<p>Plus: +</p> + +<p>Minus: -</p> + +<hr/> + +<h1 id="links">Links</h1> + +<h2 id="explicit">Explicit</h2> + +<p>Just a <a href="/url/" title="">URL</a>.</p> + +<p><a href="/url/" title="title">URL and title</a>.</p> + +<p><a href="/url/" title="title preceded by two spaces">URL and title</a>.</p> + +<p><a href="/url/" title="title preceded by a tab">URL and title</a>.</p> + +<p><a href="/url/" title="title with "quotes" in it">URL and title</a></p> + +<p><a href="/url/" title="title with single quotes">URL and title</a></p> + +<p><a href="/url/with_underscore" title="">with_underscore</a></p> + +<p><a href="mailto:[email protected]" title="">Email link</a></p> + +<p><a href="" title="">Empty</a>.</p> + +<h2 id="reference">Reference</h2> + +<p>Foo <a href="/url/" title="">bar</a>.</p> + +<p>With <a href="/url/" title="">embedded [brackets]</a>.</p> + +<p><a href="/url/" title="">b</a> by itself should be a link.</p> + +<p>Indented <a href="/url" title="">once</a>.</p> + +<p>Indented <a href="/url" title="">twice</a>.</p> + +<p>Indented <a href="/url" title="">thrice</a>.</p> + +<p>This should [not][] be a link.</p> + +<pre><code>[not]: /url</code></pre> + +<p>Foo <a href="/url/" title="Title with "quotes" inside">bar</a>.</p> + +<p>Foo <a href="/url/" title="Title with "quote" inside">biz</a>.</p> + +<h2 id="with-ampersands">With ampersands</h2> + +<p>Here’s a <a href="http://example.com/?foo=1&bar=2" title="">link with an ampersand in the URL</a>.</p> + +<p>Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T">AT&T</a>.</p> + +<p>Here’s an <a href="/script?foo=1&bar=2" title="">inline link</a>.</p> + +<p>Here’s an <a href="/script?foo=1&bar=2" title="">inline link in pointy braces</a>.</p> + +<h2 id="autolinks">Autolinks</h2> + +<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2" title="" class="uri">http://example.com/?foo=1&bar=2</a></p> + +<ul> +<li>In a list?</li> +<li><a href="http://example.com/" title="" class="uri">http://example.com/</a></li> +<li>It should.</li> +</ul> + +<p>An e-mail address: <a href="mailto:[email protected]" title="" class="email">[email protected]</a></p> + +<blockquote> +<p>Blockquoted: <a href="http://example.com/" title="" class="uri">http://example.com/</a></p> +</blockquote> + +<p>Auto-links should not occur here: <code><http://example.com/></code></p> + +<pre><code>or here: <http://example.com/></code></pre> + +<hr/> + +<h1 id="images">Images</h1> + +<p>From “Voyage dans la Lune” by Georges Melies (1902):</p> + +<figure> +<img src="lalune.jpg" id="" alt="lalune"/><figcaption>lalune</figcaption> +</figure> + +<p>Here is a movie <img src="movie.jpg" title=""/> icon.</p> + +<hr/> + +<h1 id="footnotes">Footnotes</h1> + +<p>Here is a footnote reference,<a id="fnref1" href="#fn1"><sup>1</sup></a> and another.<a id="fnref2" href="#fn2"><sup>2</sup></a> +This should <em>not</em> be a footnote reference, because it +contains a space.[^my note] Here is an inline note.<a id="fnref3" href="#fn3"><sup>3</sup></a></p> + +<blockquote> +<p>Notes can go in quotes.<a id="fnref4" href="#fn4"><sup>4</sup></a></p> +</blockquote> + +<ol> +<li>And in list items.<a id="fnref5" href="#fn5"><sup>5</sup></a></li> +</ol> + +<p>This paragraph should not be part of the note, as it is not indented.</p> +<ol class="footnotes"> +<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote +reference. It need not be placed at the end of the document. <a href="#fnref1">↩</a></p></li> +<li id="fn2"><p>Here’s the long note. This one contains multiple +blocks.</p> + +<p>Subsequent blocks are indented to show that they belong to the +footnote (as with list items).</p> + +<pre><code> { <code> }</code></pre> + +<p>If you want, you can indent every line, but you can also be +lazy and just indent the first line of each block. <a href="#fnref2">↩</a></p></li> +<li id="fn3"><p>This +is <em>easier</em> to type. Inline notes may contain +<a href="http://google.com" title="">links</a> and <code>]</code> verbatim characters, +as well as [bracketed text]. <a href="#fnref3">↩</a></p></li> +<li id="fn4"><p>In quote. <a href="#fnref4">↩</a></p></li> +<li id="fn5"><p>In list. <a href="#fnref5">↩</a></p></li> +</ol> |
