Lua: update to latest pandoc-lua-marshal (0.1.1)

- `walk` methods are added to `Block` and `Inline` values; the methods
  are similar to `pandoc.utils.walk_block` and
  `pandoc.utils.walk_inline`, but apply to filter also to the element
  itself, and therefore return a list of element instead of a single
  element.

- Functions of name `Doc` are no longer accepted as alternatives for
  `Pandoc` filter functions. This functionality was undocumented.
This commit is contained in:
Albert Krewinkel 2021-12-06 16:55:19 +01:00 committed by John MacFarlane
parent 9cbea695c4
commit fa643ba6d7
8 changed files with 211 additions and 432 deletions

View file

@ -3,6 +3,11 @@ tests: True
flags: +embed_data_files
constraints: aeson >= 2.0.1.0
source-repository-package
type: git
location: https://github.com/pandoc/pandoc-lua-marshal.git
tag: c24be07a51a6fd5ea2e1ec244b8caf220cea5ce4
-- source-repository-package
-- type: git
-- location: https://github.com/jgm/texmath.git

View file

@ -523,8 +523,9 @@ will output:
This is the filter we use when converting `MANUAL.txt` to man
pages. It converts level-1 headers to uppercase (using
`walk_block` to transform inline elements inside headers),
removes footnotes, and replaces links with regular text.
[`walk`](#type-block:walk) to transform inline elements inside
headers), removes footnotes, and replaces links with regular
text.
``` lua
-- we use preloaded text to get a UTF-8 aware 'upper' function
@ -532,10 +533,11 @@ local text = require('text')
function Header(el)
if el.level == 1 then
return pandoc.walk_block(el, {
return el:walk {
Str = function(el)
return pandoc.Str(text.upper(el.text))
end })
end
}
end
end
@ -611,7 +613,7 @@ wordcount = {
function Pandoc(el)
-- skip metadata, just count body:
pandoc.walk_block(pandoc.Div(el.blocks), wordcount)
el.blocks:walk(wordcount)
print(words .. " words in body")
os.exit(0)
end
@ -793,6 +795,35 @@ determined via [`pandoc.utils.equals`].
`meta`
: document meta information ([Meta] object)
### walk {#type-pandoc:walk}
`walk(self, lua_filter)`
Applies a Lua filter to the Pandoc element. Just as for
full-document filters, the order in which elements are handled
are Inline → Inlines → Block → Blocks → Meta → Pandoc.
Parameters:
`self`
: the element ([Pandoc](#type-pandoc))
`lua_filter`
: map of filter functions (table)
Result:
- filtered document ([Pandoc][])
Usage:
-- returns `pandoc.Pandoc{pandoc.Para{pandoc.Str 'Bye'}}`
return pandoc.Pandoc{pandoc.Para('Hi')}:walk {
Str = function (_) return 'Bye' end,
}
## Meta {#type-meta}
Meta information on a document; string-indexed collection of
@ -834,6 +865,40 @@ or `pandoc.Blocks`.
Object equality is determined via [`pandoc.utils.equals`].
### Common Methods
#### walk {#type-block:walk}
`walk(self, lua_filter)`
Applies a Lua filter to the block element. Just as for
full-document filters, the order in which elements are handled
are Inline → Inlines → Block → Blocks.
Note that the filter is applied to the subtree, but not to the
element itself. The rationale is that the element might be
deleted by the filter, leading to possibly unexpected results.
Parameters:
`self`
: the element ([Block](#type-block))
`lua_filter`
: map of filter functions (table)
Result:
- filtered block ([Block][])
Usage:
-- returns `pandoc.Para{pandoc.Str 'Bye'}`
return pandoc.Para('Hi'):walk {
Str = function (_) return 'Bye' end,
}
### BlockQuote {#type-blockquote}
A block quote element.
@ -1141,11 +1206,80 @@ into Blocks wherever a value of this type is expected:
the string into words (see [Inlines](#type-inlines)), and
then wrapping the result into a Plain singleton.
### Methods
Lists of type `Blocks` share all methods available in generic
lists, see the [`pandoc.List` module](#module-pandoc.list).
Additionally, the following methods are available on Blocks
values:
#### walk {#type-blocks:walk}
`walk(self, lua_filter)`
Applies a Lua filter to the Blocks list. Just as for
full-document filters, the order in which elements are handled
are are Inline → Inlines → Block → Blocks. The filter is applied
to all list items *and* to the list itself.
Parameters:
`self`
: the list ([Blocks](#type-blocks))
`lua_filter`
: map of filter functions (table)
Result:
- filtered list ([Blocks](#type-blocks))
Usage:
-- returns `pandoc.Blocks{pandoc.Para('Salve!')}`
return pandoc.Blocks{pandoc.Plain('Salve!)}:walk {
Plain = function (p) return pandoc.Para(p.content) end,
}
## Inline {#type-inline}
Object equality is determined by checking the Haskell
representation for equality.
### Common Methods
#### walk {#type-inline:walk}
`walk(self, lua_filter)`
Applies a Lua filter to the Inline element. Just as for
full-document filters, the order in which elements are handled
are are Inline → Inlines → Block → Blocks.
Note that the filter is applied to the subtree, but *not* to the
element itself. The rationale is that the element might be
deleted by the filter, leading to possibly unexpected results.
Parameters:
`self`
: the element ([Inline](#type-inline))
`lua_filter`
: map of filter functions (table)
Result:
- filtered inline element ([Inline][])
Usage:
-- returns `pandoc.SmallCaps('SPQR)`
return pandoc.SmallCaps('spqr'):walk {
Str = function (s) return string.upper(s.text) end,
}
### Cite {#type-cite}
Citation.
@ -1526,6 +1660,43 @@ into Blocks wherever a value of this type is expected:
into [SoftBreak](#type-softbreak) elements, and other
whitespace characters into [Spaces](#type-space).
### Methods
Lists of type `Inlines` share all methods available in generic
lists, see the [`pandoc.List` module](#module-pandoc.list).
Additionally, the following methods are available on *Inlines*
values:
#### walk {#type-inlines:walk}
`walk(self, lua_filter)`
Applies a Lua filter to the Inlines list. Just as for
full-document filters, the order in which elements are handled
are are Inline → Inlines → Block → Blocks. The filter is applied
to all list items *and* to the list itself.
Parameters:
`self`
: the list ([Inlines](#type-inlines))
`lua_filter`
: map of filter functions (table)
Result:
- filtered list ([Inlines](#type-inlines))
Usage:
-- returns `pandoc.Inlines{pandoc.SmallCaps('SPQR)}`
return pandoc.Inlines{pandoc.Emph('spqr')}:walk {
Str = function (s) return string.upper(s.text) end,
Emph = function (e) return pandoc.SmallCaps(e.content) end,
}
## Element components

View file

@ -481,7 +481,7 @@ library
mtl >= 2.2 && < 2.3,
network >= 2.6,
network-uri >= 2.6 && < 2.8,
pandoc-lua-marshal >= 0.1.0.1 && < 0.2,
pandoc-lua-marshal >= 0.1.1 && < 0.2,
pandoc-types >= 1.22.1 && < 1.23,
parsec >= 3.1 && < 3.2,
pretty >= 1.1 && < 1.2,
@ -703,7 +703,6 @@ library
Text.Pandoc.Lua.Packages,
Text.Pandoc.Lua.PandocLua,
Text.Pandoc.Lua.Util,
Text.Pandoc.Lua.Walk,
Text.Pandoc.XML.Light,
Text.Pandoc.XML.Light.Types,
Text.Pandoc.XML.Light.Proc,

View file

@ -12,242 +12,36 @@ Stability : alpha
Types and functions for running Lua filters.
-}
module Text.Pandoc.Lua.Filter ( LuaFilterFunction
, LuaFilter
, peekLuaFilter
, runFilterFile
, walkInlines
, walkInlineLists
, walkBlocks
, walkBlockLists
, module Text.Pandoc.Lua.Walk
) where
import Control.Applicative ((<|>))
import Control.Monad (mplus, (>=>), (<$!>))
import Data.Data (Data, DataType, dataTypeConstrs, dataTypeName, dataTypeOf,
showConstr, toConstr, tyconUQname)
import Data.Foldable (foldrM)
import Data.List (foldl')
import Data.Map (Map)
import Data.String (IsString (fromString))
module Text.Pandoc.Lua.Filter
( runFilterFile
) where
import Control.Monad ((>=>), (<$!>))
import HsLua as Lua
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.ErrorConversion ()
import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Lua.Walk (List (..), SingletonsList (..))
import Text.Pandoc.Walk (Walkable (walkM))
import Text.Pandoc.Lua.Marshal.Filter
import qualified Data.Map.Strict as Map
import qualified Text.Pandoc.Lua.Util as LuaUtil
-- | Transform document using the filter defined in the given file.
runFilterFile :: FilePath -> Pandoc -> LuaE PandocError Pandoc
runFilterFile filterPath doc = do
oldtop <- Lua.gettop
oldtop <- gettop
stat <- LuaUtil.dofileWithTraceback filterPath
if stat /= Lua.OK
then Lua.throwErrorAsException
then throwErrorAsException
else do
newtop <- Lua.gettop
newtop <- gettop
-- Use the returned filters, or the implicitly defined global
-- filter if nothing was returned.
luaFilters <- if newtop - oldtop >= 1
then Lua.peek Lua.top
else Lua.pushglobaltable *> fmap (:[]) Lua.popValue
luaFilters <- forcePeek $
if newtop - oldtop >= 1
then peekList peekFilter top
else (:[]) <$!> (liftLua pushglobaltable *> peekFilter top)
settop oldtop
runAll luaFilters doc
runAll :: [LuaFilter] -> Pandoc -> LuaE PandocError Pandoc
runAll = foldr ((>=>) . walkMWithLuaFilter) return
-- | Filter function stored in the registry
newtype LuaFilterFunction = LuaFilterFunction Lua.Reference
-- | Collection of filter functions (at most one function per element
-- constructor)
newtype LuaFilter = LuaFilter (Map Name LuaFilterFunction)
instance Peekable LuaFilter where
peek = Lua.forcePeek . peekLuaFilter
-- | Retrieves a LuaFilter object from the stack.
peekLuaFilter :: LuaError e => Peeker e LuaFilter
peekLuaFilter idx = do
let constrs = listOfInlinesFilterName
: listOfBlocksFilterName
: metaFilterName
: pandocFilterNames
++ blockElementNames
++ inlineElementNames
let go constr acc = Lua.liftLua $ do
Lua.getfield idx constr
filterFn <- registerFilterFunction
return $ case filterFn of
Nothing -> acc
Just fn -> Map.insert constr fn acc
LuaFilter <$!> foldrM go Map.empty constrs
-- | Register the function at the top of the stack as a filter function in the
-- registry.
registerFilterFunction :: LuaError e => LuaE e (Maybe LuaFilterFunction)
registerFilterFunction = do
isFn <- Lua.isfunction Lua.top
if isFn
then Just . LuaFilterFunction <$> Lua.ref Lua.registryindex
else Nothing <$ Lua.pop 1
-- | Retrieve filter function from registry and push it to the top of the stack.
pushFilterFunction :: LuaFilterFunction -> LuaE PandocError ()
pushFilterFunction (LuaFilterFunction fnRef) =
Lua.getref Lua.registryindex fnRef
-- | Fetch either a list of elements from the stack. If there is a single
-- element instead of a list, fetch that element as a singleton list. If the top
-- of the stack is nil, return the default element that was passed to this
-- function. If none of these apply, raise an error.
elementOrList :: Peeker PandocError a -> a -> LuaE PandocError [a]
elementOrList p x = do
elementUnchanged <- Lua.isnil top
if elementUnchanged
then [x] <$ pop 1
else forcePeek . (`lastly` pop 1) $ (((:[]) <$!> p top) <|> peekList p top)
-- | Fetches a single element; returns the fallback if the value is @nil@.
singleElement :: forall a e. (LuaError e) => Peeker e a -> a -> LuaE e a
singleElement p x = do
elementUnchanged <- Lua.isnil top
if elementUnchanged
then x <$ Lua.pop 1
else forcePeek $ p top `lastly` pop 1
-- | Pop and return a value from the stack; if the value at the top of
-- the stack is @nil@, return the fallback element.
popOption :: Peeker PandocError a -> a -> LuaE PandocError a
popOption peeker fallback = forcePeek . (`lastly` pop 1) $
(fallback <$ peekNil top) <|> peeker top
-- | Apply filter on a sequence of AST elements. Both lists and single
-- value are accepted as filter function return values.
runOnSequence :: forall a. (Data a, Pushable a)
=> Peeker PandocError a -> LuaFilter -> SingletonsList a
-> LuaE PandocError (SingletonsList a)
runOnSequence peeker (LuaFilter fnMap) (SingletonsList xs) =
SingletonsList <$> mconcatMapM tryFilter xs
where
tryFilter :: a -> LuaE PandocError [a]
tryFilter x =
let filterFnName = fromString $ showConstr (toConstr x)
catchAllName = fromString . tyconUQname $ dataTypeName (dataTypeOf x)
in case Map.lookup filterFnName fnMap <|> Map.lookup catchAllName fnMap of
Just fn -> runFilterFunction fn x *> elementOrList peeker x
Nothing -> return [x]
-- | Try filtering the given value without type error corrections on
-- the return value.
runOnValue :: (Data a, Pushable a)
=> Name -> Peeker PandocError a
-> LuaFilter -> a
-> LuaE PandocError a
runOnValue filterFnName peeker (LuaFilter fnMap) x =
case Map.lookup filterFnName fnMap of
Just fn -> runFilterFunction fn x *> popOption peeker x
Nothing -> return x
-- | Push a value to the stack via a Lua filter function. The filter
-- function is called with the given element as argument and is expected
-- to return an element. Alternatively, the function can return nothing
-- or nil, in which case the element is left unchanged.
runFilterFunction :: Pushable a
=> LuaFilterFunction -> a -> LuaE PandocError ()
runFilterFunction lf x = do
pushFilterFunction lf
Lua.push x
LuaUtil.callWithTraceback 1 1
walkMWithLuaFilter :: LuaFilter -> Pandoc -> LuaE PandocError Pandoc
walkMWithLuaFilter f =
walkInlines f
>=> walkInlineLists f
>=> walkBlocks f
>=> walkBlockLists f
>=> walkMeta f
>=> walkPandoc f
mconcatMapM :: (Monad m) => (a -> m [a]) -> [a] -> m [a]
mconcatMapM f = fmap mconcat . mapM f
hasOneOf :: LuaFilter -> [Name] -> Bool
hasOneOf (LuaFilter fnMap) = any (`Map.member` fnMap)
contains :: LuaFilter -> Name -> Bool
contains (LuaFilter fnMap) = (`Map.member` fnMap)
walkInlines :: Walkable (SingletonsList Inline) a
=> LuaFilter -> a -> LuaE PandocError a
walkInlines lf =
let f :: SingletonsList Inline -> LuaE PandocError (SingletonsList Inline)
f = runOnSequence peekInline lf
in if lf `hasOneOf` inlineElementNames
then walkM f
else return
walkInlineLists :: Walkable (List Inline) a
=> LuaFilter -> a -> LuaE PandocError a
walkInlineLists lf =
let f :: List Inline -> LuaE PandocError (List Inline)
f = runOnValue listOfInlinesFilterName peekListOfInlines lf
peekListOfInlines idx = List <$!> (peekInlinesFuzzy idx)
in if lf `contains` listOfInlinesFilterName
then walkM f
else return
walkBlocks :: Walkable (SingletonsList Block) a
=> LuaFilter -> a -> LuaE PandocError a
walkBlocks lf =
let f :: SingletonsList Block -> LuaE PandocError (SingletonsList Block)
f = runOnSequence peekBlock lf
in if lf `hasOneOf` blockElementNames
then walkM f
else return
walkBlockLists :: Walkable (List Block) a
=> LuaFilter -> a -> LuaE PandocError a
walkBlockLists lf =
let f :: List Block -> LuaE PandocError (List Block)
f = runOnValue listOfBlocksFilterName peekListOfBlocks lf
peekListOfBlocks idx = List <$!> (peekBlocksFuzzy idx)
in if lf `contains` listOfBlocksFilterName
then walkM f
else return
walkMeta :: LuaFilter -> Pandoc -> LuaE PandocError Pandoc
walkMeta lf (Pandoc m bs) = do
m' <- runOnValue "Meta" peekMeta lf m
return $ Pandoc m' bs
walkPandoc :: LuaFilter -> Pandoc -> LuaE PandocError Pandoc
walkPandoc (LuaFilter fnMap) =
case foldl' mplus Nothing (map (`Map.lookup` fnMap) pandocFilterNames) of
Just fn -> \x -> runFilterFunction fn x *> singleElement peekPandoc x
Nothing -> return
constructorsFor :: DataType -> [Name]
constructorsFor x = map (fromString . show) (dataTypeConstrs x)
inlineElementNames :: [Name]
inlineElementNames = "Inline" : constructorsFor (dataTypeOf (Str mempty))
blockElementNames :: [Name]
blockElementNames = "Block" : constructorsFor (dataTypeOf (Para []))
listOfInlinesFilterName :: Name
listOfInlinesFilterName = "Inlines"
listOfBlocksFilterName :: Name
listOfBlocksFilterName = "Blocks"
metaFilterName :: Name
metaFilterName = "Meta"
pandocFilterNames :: [Name]
pandocFilterNames = ["Pandoc", "Doc"]
runAll :: [Filter] -> Pandoc -> LuaE PandocError Pandoc
runAll = foldr ((>=>) . applyFully) return

View file

@ -31,20 +31,16 @@ import HsLua.Class.Peekable (PeekError)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class.PandocIO (runIO)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Filter (List (..), SingletonsList (..), LuaFilter,
peekLuaFilter,
walkInlines, walkInlineLists,
walkBlocks, walkBlockLists)
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)
, pushReaderOptions)
import Text.Pandoc.Lua.Module.Utils (sha1)
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader)
import Text.Pandoc.Walk (Walkable)
import qualified HsLua as Lua
import qualified Data.ByteString.Lazy as BL
@ -149,16 +145,6 @@ stringConstants =
}
in map toField nullaryConstructors
walkElement :: (Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a,
Walkable (List Inline) a,
Walkable (List Block) a)
=> a -> LuaFilter -> LuaE PandocError a
walkElement x f = walkInlines f x
>>= walkInlineLists f
>>= walkBlocks f
>>= walkBlockLists f
functions :: [DocumentedFunction PandocError]
functions =
[ defun "pipe"
@ -206,15 +192,21 @@ functions =
, defun "walk_block"
### walkElement
<#> parameter peekBlockFuzzy "Block" "block" "element to traverse"
<#> parameter peekLuaFilter "LuaFilter" "filter" "filter functions"
<#> parameter peekFilter "Filter" "lua_filter" "filter functions"
=#> functionResult pushBlock "Block" "modified Block"
, defun "walk_inline"
### walkElement
<#> parameter peekInlineFuzzy "Inline" "inline" "element to traverse"
<#> parameter peekLuaFilter "LuaFilter" "filter" "filter functions"
<#> parameter peekFilter "Filter" "lua_filter" "filter functions"
=#> functionResult pushInline "Inline" "modified Inline"
]
where
walkElement x f =
walkInlineSplicing f x
>>= walkInlinesStraight f
>>= walkBlockSplicing f
>>= walkBlocksStraight f
data PipeError = PipeError
{ pipeErrorCommand :: T.Text

View file

@ -1,183 +0,0 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{- |
Module : Text.Pandoc.Lua.Walk
Copyright : © 2012-2021 John MacFarlane,
© 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability : alpha
Walking documents in a filter-suitable way.
-}
module Text.Pandoc.Lua.Walk
( SingletonsList (..)
, List (..)
)
where
import Control.Monad ((<=<))
import Data.Data (Data)
import HsLua (Pushable (push))
import Text.Pandoc.Lua.Marshal.AST (pushBlocks, pushInlines)
import Text.Pandoc.Definition
import Text.Pandoc.Walk
-- | Helper type which allows to traverse trees in order, while splicing in
-- trees.
--
-- The only interesting use of this type is via it's '@Walkable@' instance. That
-- instance makes it possible to walk a Pandoc document (or a subset thereof),
-- while applying a function on each element of an AST element /list/, and have
-- the resulting list spliced back in place of the original element. This is the
-- traversal/splicing method used for Lua filters.
newtype SingletonsList a = SingletonsList { singletonsList :: [a] }
deriving (Functor, Foldable, Traversable)
--
-- SingletonsList Inline
--
instance {-# OVERLAPPING #-} Walkable (SingletonsList Inline) [Inline] where
walkM = walkSingletonsListM
query = querySingletonsList
instance Walkable (SingletonsList Inline) Pandoc where
walkM = walkPandocM
query = queryPandoc
instance Walkable (SingletonsList Inline) Citation where
walkM = walkCitationM
query = queryCitation
instance Walkable (SingletonsList Inline) Inline where
walkM = walkInlineM
query = queryInline
instance Walkable (SingletonsList Inline) Block where
walkM = walkBlockM
query = queryBlock
instance Walkable (SingletonsList Inline) Row where
walkM = walkRowM
query = queryRow
instance Walkable (SingletonsList Inline) TableHead where
walkM = walkTableHeadM
query = queryTableHead
instance Walkable (SingletonsList Inline) TableBody where
walkM = walkTableBodyM
query = queryTableBody
instance Walkable (SingletonsList Inline) TableFoot where
walkM = walkTableFootM
query = queryTableFoot
instance Walkable (SingletonsList Inline) Caption where
walkM = walkCaptionM
query = queryCaption
instance Walkable (SingletonsList Inline) Cell where
walkM = walkCellM
query = queryCell
instance Walkable (SingletonsList Inline) MetaValue where
walkM = walkMetaValueM
query = queryMetaValue
instance Walkable (SingletonsList Inline) Meta where
walkM f (Meta metamap) = Meta <$> walkM f metamap
query f (Meta metamap) = query f metamap
--
-- SingletonsList Block
--
instance {-# OVERLAPPING #-} Walkable (SingletonsList Block) [Block] where
walkM = walkSingletonsListM
query = querySingletonsList
instance Walkable (SingletonsList Block) Pandoc where
walkM = walkPandocM
query = queryPandoc
instance Walkable (SingletonsList Block) Citation where
walkM = walkCitationM
query = queryCitation
instance Walkable (SingletonsList Block) Inline where
walkM = walkInlineM
query = queryInline
instance Walkable (SingletonsList Block) Block where
walkM = walkBlockM
query = queryBlock
instance Walkable (SingletonsList Block) Row where
walkM = walkRowM
query = queryRow
instance Walkable (SingletonsList Block) TableHead where
walkM = walkTableHeadM
query = queryTableHead
instance Walkable (SingletonsList Block) TableBody where
walkM = walkTableBodyM
query = queryTableBody
instance Walkable (SingletonsList Block) TableFoot where
walkM = walkTableFootM
query = queryTableFoot
instance Walkable (SingletonsList Block) Caption where
walkM = walkCaptionM
query = queryCaption
instance Walkable (SingletonsList Block) Cell where
walkM = walkCellM
query = queryCell
instance Walkable (SingletonsList Block) MetaValue where
walkM = walkMetaValueM
query = queryMetaValue
instance Walkable (SingletonsList Block) Meta where
walkM f (Meta metamap) = Meta <$> walkM f metamap
query f (Meta metamap) = query f metamap
walkSingletonsListM :: (Monad m, Walkable (SingletonsList a) a)
=> (SingletonsList a -> m (SingletonsList a))
-> [a] -> m [a]
walkSingletonsListM f =
let f' = fmap singletonsList . f . SingletonsList . (:[]) <=< walkM f
in fmap mconcat . mapM f'
querySingletonsList :: (Monoid c, Walkable (SingletonsList a) a)
=> (SingletonsList a -> c)
-> [a] -> c
querySingletonsList f =
let f' x = f (SingletonsList [x]) `mappend` query f x
in mconcat . map f'
-- | List wrapper where each list is processed as a whole, but special
-- pushed to Lua in type-dependent ways.
--
-- The walk instance is basically that of unwrapped Haskell lists.
newtype List a = List { fromList :: [a] }
deriving (Data, Eq, Show)
instance Pushable (List Block) where
push (List xs) = pushBlocks xs
instance Pushable (List Inline) where
push (List xs) = pushInlines xs
instance Walkable [a] b => Walkable (List a) b where
walkM f = walkM (fmap fromList . f . List)
query f = query (f . List)

View file

@ -26,7 +26,6 @@ extra-deps:
- lua-2.0.2
- tasty-hslua-1.0.0
- tasty-lua-1.0.0
- pandoc-lua-marshal-0.1.0.1
- pandoc-types-1.22.1
- commonmark-0.2.1.1
- commonmark-extensions-0.2.2
@ -37,6 +36,8 @@ extra-deps:
- unicode-data-0.2.0
- git: https://github.com/jgm/ipynb.git
commit: 00246af10885c2ad4413ace4f69a7e6c88297a08
- git: https://github.com/pandoc/pandoc-lua-marshal.git
commit: c24be07a51a6fd5ea2e1ec244b8caf220cea5ce4
ghc-options:
"$locals": -fhide-source-paths -Wno-missing-home-modules
resolver: lts-18.10

View file

@ -1,4 +1,4 @@
function Doc (doc)
function Pandoc (doc)
local meta = {}
local hello = { pandoc.Str "Hello,", pandoc.Space(), pandoc.Str "World!" }
local blocks = { pandoc.Para(hello) }