aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling/List.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2020-01-15 23:26:00 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2020-01-15 14:26:00 -0800
commit672a4bdd1d4a587feaa38613fce64335adaad76d (patch)
tree17e58c93a24eedba8fc06aa28f661395e1057096 /src/Text/Pandoc/Lua/Marshaling/List.hs
parent400b29d10e9ba20479692ff2e2a482bb27bfe09f (diff)
downloadpandoc-672a4bdd1d4a587feaa38613fce64335adaad76d.tar.gz
Lua filters: allow filtering of element lists (#6040)
Lists of Inline and Block elements can now be filtered via `Inlines` and `Blocks` functions, respectively. This is helpful if a filter conversion depends on the order of elements rather than a single element. For example, the following filter can be used to remove all spaces before a citation: function isSpaceBeforeCite (spc, cite) return spc and spc.t == 'Space' and cite and cite.t == 'Cite' end function Inlines (inlines) for i = #inlines-1,1,-1 do if isSpaceBeforeCite(inlines[i], inlines[i+1]) then inlines:remove(i) end end return inlines end Closes: #6038
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling/List.hs')
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/List.hs45
1 files changed, 45 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/List.hs b/src/Text/Pandoc/Lua/Marshaling/List.hs
new file mode 100644
index 000000000..e4fbfc200
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshaling/List.hs
@@ -0,0 +1,45 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE UndecidableInstances #-}
+{- |
+Module : Text.Pandoc.Lua.Marshaling.List
+Copyright : © 2012-2020 John MacFarlane
+ © 2017-2020 Albert Krewinkel
+License : GNU GPL, version 2 or above
+Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+Stability : alpha
+
+Marshaling/unmarshaling instances for @pandoc.List@s.
+-}
+module Text.Pandoc.Lua.Marshaling.List
+ ( List (..)
+ ) where
+
+import Prelude
+import Data.Data (Data)
+import Foreign.Lua (Peekable, Pushable)
+import Text.Pandoc.Walk (Walkable (..))
+import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
+
+import qualified Foreign.Lua as Lua
+
+-- | List wrapper which is marshalled as @pandoc.List@.
+newtype List a = List { fromList :: [a] }
+ deriving (Data, Eq, Show)
+
+instance Pushable a => Pushable (List a) where
+ push (List xs) =
+ pushViaConstructor "List" xs
+
+instance Peekable a => Peekable (List a) where
+ peek idx = defineHowTo "get List" $ do
+ xs <- Lua.peek idx
+ return $ List xs
+
+-- List is just a wrapper, so we can reuse the walk instance for
+-- unwrapped Hasekll lists.
+instance Walkable [a] b => Walkable (List a) b where
+ walkM f = walkM (fmap fromList . f . List)
+ query f = query (f . List)