diff options
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/Pandoc.hs')
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Pandoc.hs | 168 |
1 files changed, 141 insertions, 27 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs index bc9ddc5e5..f08914eba 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -16,13 +16,14 @@ module Text.Pandoc.Lua.Module.Pandoc ) where import Prelude hiding (read) -import Control.Applicative (optional) -import Control.Monad ((>=>), forM_, when) +import Control.Applicative ((<|>), optional) +import Control.Monad ((>=>), (<$!>), forM_, when) import Control.Monad.Catch (catch, throwM) import Control.Monad.Except (throwError) import Data.Default (Default (..)) import Data.Maybe (fromMaybe) -import HsLua as Lua hiding (pushModule) +import Data.Text (Text) +import HsLua as Lua hiding (Div, pushModule) import HsLua.Class.Peekable (PeekError) import System.Exit (ExitCode (..)) import Text.Pandoc.Class.PandocIO (runIO) @@ -65,20 +66,25 @@ pushModule = do pushDocumentedFunction fn rawset (nth 3) forM_ otherConstructors addConstr + forM_ blockConstructors addConstr forM_ inlineConstructors addConstr - -- add constructors to Inlines.constructor - newtable -- constructor - forM_ (inlineConstructors @PandocError) $ \fn -> do - let name = functionName fn - pushName name - pushName name - rawget (nth 4) - rawset (nth 3) - -- set as pandoc.Inline.constructor - pushName "Inline" - newtable *> pushName "constructor" *> pushvalue (nth 4) *> rawset (nth 3) - rawset (nth 4) - pop 1 -- remaining constructor table + let addConstructorTable constructors = do + -- add constructors to Inlines.constructor + newtable -- constructor + forM_ constructors $ \fn -> do + let name = functionName fn + pushName name + pushName name + rawget (nth 4) + rawset (nth 3) + -- set as pandoc.Inline.constructor + pushName "Inline" + newtable *> pushName "constructor" *> + pushvalue (nth 4) *> rawset (nth 3) + rawset (nth 4) + pop 1 -- remaining constructor table + addConstructorTable (blockConstructors @PandocError) + addConstructorTable (inlineConstructors @PandocError) return 1 inlineConstructors :: LuaError e => [DocumentedFunction e] @@ -86,7 +92,7 @@ inlineConstructors = [ defun "Cite" ### liftPure2 Cite <#> parameter (peekList peekCitation) "citations" "list of Citations" "" - <#> parameter peekFuzzyInlines "content" "Inline" "placeholder content" + <#> parameter peekInlinesFuzzy "content" "Inline" "placeholder content" =#> functionResult pushInline "Inline" "cite element" , defun "Code" ### liftPure2 (flip Code) @@ -99,7 +105,7 @@ inlineConstructors = let attr = fromMaybe nullAttr mattr title = fromMaybe mempty mtitle in Image attr caption (src, title)) - <#> parameter peekFuzzyInlines "Inlines" "caption" "image caption / alt" + <#> parameter peekInlinesFuzzy "Inlines" "caption" "image caption / alt" <#> parameter peekText "string" "src" "path/URL of the image file" <#> optionalParameter peekText "string" "title" "brief image description" <#> optionalParameter peekAttr "Attr" "attr" "image attributes" @@ -112,7 +118,7 @@ inlineConstructors = let attr = fromMaybe nullAttr mattr title = fromMaybe mempty mtitle in Link attr content (target, title)) - <#> parameter peekFuzzyInlines "Inlines" "content" "text for this link" + <#> parameter peekInlinesFuzzy "Inlines" "content" "text for this link" <#> parameter peekText "string" "target" "the link target" <#> optionalParameter peekText "string" "title" "brief link description" <#> optionalParameter peekAttr "Attr" "attr" "link attributes" @@ -124,12 +130,12 @@ inlineConstructors = =#> functionResult pushInline "Inline" "math element" , defun "Note" ### liftPure Note - <#> parameter peekFuzzyBlocks "content" "Blocks" "note content" + <#> parameter peekBlocksFuzzy "content" "Blocks" "note content" =#> functionResult pushInline "Inline" "note" , defun "Quoted" ### liftPure2 Quoted <#> parameter peekQuoteType "quotetype" "QuoteType" "type of quotes" - <#> parameter peekFuzzyInlines "content" "Inlines" "inlines in quotes" + <#> parameter peekInlinesFuzzy "content" "Inlines" "inlines in quotes" =#> functionResult pushInline "Inline" "quoted element" , defun "RawInline" ### liftPure2 RawInline @@ -145,11 +151,11 @@ inlineConstructors = =#> functionResult pushInline "Inline" "new space" , defun "Span" ### liftPure2 (\inlns mattr -> Span (fromMaybe nullAttr mattr) inlns) - <#> parameter peekFuzzyInlines "content" "Inlines" "inline content" + <#> parameter peekInlinesFuzzy "content" "Inlines" "inline content" <#> optionalParameter peekAttr "attr" "Attr" "additional attributes" =#> functionResult pushInline "Inline" "span element" , defun "Str" - ### liftPure (\s -> s `seq` Str s) + ### liftPure Str <#> parameter peekText "text" "string" "" =#> functionResult pushInline "Inline" "new Str object" , mkInlinesConstr "Strong" Strong @@ -159,11 +165,119 @@ inlineConstructors = , mkInlinesConstr "Underline" Underline ] +blockConstructors :: LuaError e => [DocumentedFunction e] +blockConstructors = + [ defun "BlockQuote" + ### liftPure BlockQuote + <#> blocksParam + =#> blockResult "BlockQuote element" + + , defun "BulletList" + ### liftPure BulletList + <#> blockItemsParam "list items" + =#> blockResult "BulletList element" + + , defun "CodeBlock" + ### liftPure2 (\code mattr -> CodeBlock (fromMaybe nullAttr mattr) code) + <#> textParam "text" "code block content" + <#> optAttrParam + =#> blockResult "CodeBlock element" + + , defun "DefinitionList" + ### liftPure DefinitionList + <#> parameter (choice + [ peekList peekDefinitionItem + , \idx -> (:[]) <$!> peekDefinitionItem idx + ]) + "{{Inlines, {Blocks,...}},...}" + "content" "definition items" + =#> blockResult "DefinitionList element" + + , defun "Div" + ### liftPure2 (\content mattr -> Div (fromMaybe nullAttr mattr) content) + <#> blocksParam + <#> optAttrParam + =#> blockResult "Div element" + + , defun "Header" + ### liftPure3 (\lvl content mattr -> + Header lvl (fromMaybe nullAttr mattr) content) + <#> parameter peekIntegral "integer" "level" "heading level" + <#> parameter peekInlinesFuzzy "Inlines" "content" "inline content" + <#> optAttrParam + =#> blockResult "Header element" + + , defun "HorizontalRule" + ### return HorizontalRule + =#> blockResult "HorizontalRule element" + + , defun "LineBlock" + ### liftPure LineBlock + <#> parameter (peekList peekInlinesFuzzy) "{Inlines,...}" "content" "lines" + =#> blockResult "LineBlock element" + + , defun "Null" + ### return Null + =#> blockResult "Null element" + + , defun "OrderedList" + ### liftPure2 (\items mListAttrib -> + let defListAttrib = (1, DefaultStyle, DefaultDelim) + in OrderedList (fromMaybe defListAttrib mListAttrib) items) + <#> blockItemsParam "ordered list items" + <#> optionalParameter peekListAttributes "ListAttributes" "listAttributes" + "specifier for the list's numbering" + =#> blockResult "OrderedList element" + + , defun "Para" + ### liftPure Para + <#> parameter peekInlinesFuzzy "Inlines" "content" "paragraph content" + =#> blockResult "Para element" + + , defun "Plain" + ### liftPure Plain + <#> parameter peekInlinesFuzzy "Inlines" "content" "paragraph content" + =#> blockResult "Plain element" + + , defun "RawBlock" + ### liftPure2 RawBlock + <#> parameter peekFormat "Format" "format" "format of content" + <#> parameter peekText "string" "text" "raw content" + =#> blockResult "RawBlock element" + + , defun "Table" + ### (\capt colspecs thead tbodies tfoot mattr -> + let attr = fromMaybe nullAttr mattr + in return $! attr `seq` capt `seq` colspecs `seq` thead `seq` tbodies + `seq` tfoot `seq` Table attr capt colspecs thead tbodies tfoot) + <#> parameter peekCaption "Caption" "caption" "table caption" + <#> parameter (peekList peekColSpec) "{ColSpec,...}" "colspecs" + "column alignments and widths" + <#> parameter peekTableHead "TableHead" "head" "table head" + <#> parameter (peekList peekTableBody) "{TableBody,...}" "bodies" + "table bodies" + <#> parameter peekTableFoot "TableFoot" "foot" "table foot" + <#> optAttrParam + =#> blockResult "Table element" + ] + where + blockResult = functionResult pushBlock "Block" + blocksParam = parameter peekBlocksFuzzy "Blocks" "content" "block content" + blockItemsParam = parameter peekItemsFuzzy "List of Blocks" "content" + peekItemsFuzzy idx = peekList peekBlocksFuzzy idx + <|> ((:[]) <$!> peekBlocksFuzzy idx) + +textParam :: LuaError e => Text -> Text -> Parameter e Text +textParam = parameter peekText "string" + +optAttrParam :: LuaError e => Parameter e (Maybe Attr) +optAttrParam = optionalParameter peekAttr "attr" "Attr" "additional attributes" + mkInlinesConstr :: LuaError e => Name -> ([Inline] -> Inline) -> DocumentedFunction e mkInlinesConstr name constr = defun name ### liftPure (\x -> x `seq` constr x) - <#> parameter peekFuzzyInlines "content" "Inlines" "" + <#> parameter peekInlinesFuzzy "content" "Inlines" "" =#> functionResult pushInline "Inline" "new object" otherConstructors :: LuaError e => [DocumentedFunction e] @@ -181,8 +295,8 @@ otherConstructors = }) <#> parameter peekText "string" "cid" "citation ID (e.g. bibtex key)" <#> parameter peekRead "citation mode" "mode" "citation rendering mode" - <#> optionalParameter peekFuzzyInlines "prefix" "Inlines" "" - <#> optionalParameter peekFuzzyInlines "suffix" "Inlines" "" + <#> optionalParameter peekInlinesFuzzy "prefix" "Inlines" "" + <#> optionalParameter peekInlinesFuzzy "suffix" "Inlines" "" <#> optionalParameter peekIntegral "note_num" "integer" "note number" <#> optionalParameter peekIntegral "hash" "integer" "hash number" =#> functionResult pushCitation "Citation" "new citation object" @@ -283,7 +397,7 @@ pushPipeError pipeErr = do mkPandoc :: PandocLua NumResults mkPandoc = liftPandocLua $ do doc <- forcePeek $ do - blks <- peekBlocks (nthBottom 1) + blks <- peekBlocksFuzzy (nthBottom 1) mMeta <- optional $ peekMeta (nthBottom 2) pure $ Pandoc (fromMaybe nullMeta mMeta) blks pushPandoc doc |