aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2018-09-24 20:11:00 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2018-09-24 20:11:27 +0200
commit56fe5b559e9dbda97840a45c9f3a0713e2913bb5 (patch)
treeb366cb73f09271508f99b55eb479b1bb5cb3c2f1 /src/Text/Pandoc/Writers
parent0272e63527e0b06644e178c51508baf1cf96afa2 (diff)
downloadpandoc-56fe5b559e9dbda97840a45c9f3a0713e2913bb5.tar.gz
Use hslua v1.0.0
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs143
1 files changed, 74 insertions, 69 deletions
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 866df85be..1d1261baf 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -1,6 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{- Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
@@ -35,25 +35,26 @@ import Prelude
import Control.Arrow ((***))
import Control.Exception
import Control.Monad (when)
-import Control.Monad.Trans (MonadIO (liftIO))
import Data.Char (toLower)
import Data.List (intersperse)
import qualified Data.Map as M
import Data.Text (Text, pack)
import Data.Typeable
-import Foreign.Lua (Lua, ToLuaStack (..), callFunc)
-import Foreign.Lua.Api
+import Foreign.Lua (Lua, Pushable)
import Text.Pandoc.Class (PandocIO)
import Text.Pandoc.Definition
import Text.Pandoc.Error
-import Text.Pandoc.Lua.Init (runPandocLua, registerScriptPath)
+import Text.Pandoc.Lua.Init (LuaException (LuaException), runPandocLua,
+ registerScriptPath)
import Text.Pandoc.Lua.StackInstances ()
-import Text.Pandoc.Lua.Util (addField, addValue, dostring')
+import Text.Pandoc.Lua.Util (addField)
import Text.Pandoc.Options
import Text.Pandoc.Templates
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Writers.Shared
+import qualified Foreign.Lua as Lua
+
attrToMap :: Attr -> M.Map String String
attrToMap (id',classes,keyvals) = M.fromList
$ ("id", id')
@@ -62,26 +63,26 @@ attrToMap (id',classes,keyvals) = M.fromList
newtype Stringify a = Stringify a
-instance ToLuaStack (Stringify Format) where
- push (Stringify (Format f)) = push (map toLower f)
+instance Pushable (Stringify Format) where
+ push (Stringify (Format f)) = Lua.push (map toLower f)
-instance ToLuaStack (Stringify [Inline]) where
- push (Stringify ils) = push =<< inlineListToCustom ils
+instance Pushable (Stringify [Inline]) where
+ push (Stringify ils) = Lua.push =<< inlineListToCustom ils
-instance ToLuaStack (Stringify [Block]) where
- push (Stringify blks) = push =<< blockListToCustom blks
+instance Pushable (Stringify [Block]) where
+ push (Stringify blks) = Lua.push =<< blockListToCustom blks
-instance ToLuaStack (Stringify MetaValue) where
- push (Stringify (MetaMap m)) = push (fmap Stringify m)
- push (Stringify (MetaList xs)) = push (map Stringify xs)
- push (Stringify (MetaBool x)) = push x
- push (Stringify (MetaString s)) = push s
- push (Stringify (MetaInlines ils)) = push (Stringify ils)
- push (Stringify (MetaBlocks bs)) = push (Stringify bs)
+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 ToLuaStack (Stringify Citation) where
+instance Pushable (Stringify Citation) where
push (Stringify cit) = do
- createtable 6 0
+ Lua.createtable 6 0
addField "citationId" $ citationId cit
addField "citationPrefix" . Stringify $ citationPrefix cit
addField "citationSuffix" . Stringify $ citationSuffix cit
@@ -93,10 +94,12 @@ instance ToLuaStack (Stringify Citation) where
-- associated value.
newtype KeyValue a b = KeyValue (a, b)
-instance (ToLuaStack a, ToLuaStack b) => ToLuaStack (KeyValue a b) where
+instance (Pushable a, Pushable b) => Pushable (KeyValue a b) where
push (KeyValue (k, v)) = do
- newtable
- addValue k v
+ Lua.newtable
+ Lua.push k
+ Lua.push v
+ Lua.rawset (Lua.nthFromTop 3)
data PandocLuaException = PandocLuaException String
deriving (Show, Typeable)
@@ -106,14 +109,13 @@ instance Exception PandocLuaException
-- | Convert Pandoc to custom markup.
writeCustom :: FilePath -> WriterOptions -> Pandoc -> PandocIO Text
writeCustom luaFile opts doc@(Pandoc meta _) = do
- luaScript <- liftIO $ UTF8.readFile luaFile
res <- runPandocLua $ do
registerScriptPath luaFile
- stat <- dostring' luaScript
+ stat <- Lua.dofile luaFile
-- check for error in lua script (later we'll change the return type
-- to handle this more gracefully):
- when (stat /= OK) $
- tostring (-1) >>= throw . PandocLuaException . UTF8.toString
+ when (stat /= Lua.OK) $
+ Lua.tostring' (-1) >>= throw . PandocLuaException . UTF8.toString
-- TODO - call hierarchicalize, so we have that info
rendered <- docToCustom opts doc
context <- metaToJSON opts
@@ -122,7 +124,7 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do
meta
return (rendered, context)
let (body, context) = case res of
- Left e -> throw (PandocLuaException (show e))
+ Left (LuaException msg) -> throw (PandocLuaException msg)
Right x -> x
case writerTemplate opts of
Nothing -> return $ pack body
@@ -134,7 +136,7 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do
docToCustom :: WriterOptions -> Pandoc -> Lua String
docToCustom opts (Pandoc (Meta metamap) blocks) = do
body <- blockListToCustom blocks
- callFunc "Doc" body (fmap Stringify metamap) (writerVariables opts)
+ Lua.callFunc "Doc" body (fmap Stringify metamap) (writerVariables opts)
-- | Convert Pandoc block element to Custom.
blockToCustom :: Block -- ^ Block element
@@ -142,52 +144,55 @@ blockToCustom :: Block -- ^ Block element
blockToCustom Null = return ""
-blockToCustom (Plain inlines) = callFunc "Plain" (Stringify inlines)
+blockToCustom (Plain inlines) = Lua.callFunc "Plain" (Stringify inlines)
blockToCustom (Para [Image attr txt (src,tit)]) =
- callFunc "CaptionedImage" src tit (Stringify txt) (attrToMap attr)
+ Lua.callFunc "CaptionedImage" src tit (Stringify txt) (attrToMap attr)
-blockToCustom (Para inlines) = callFunc "Para" (Stringify inlines)
+blockToCustom (Para inlines) = Lua.callFunc "Para" (Stringify inlines)
-blockToCustom (LineBlock linesList) = callFunc "LineBlock" (map Stringify linesList)
+blockToCustom (LineBlock linesList) =
+ Lua.callFunc "LineBlock" (map Stringify linesList)
blockToCustom (RawBlock format str) =
- callFunc "RawBlock" (Stringify format) str
+ Lua.callFunc "RawBlock" (Stringify format) str
-blockToCustom HorizontalRule = callFunc "HorizontalRule"
+blockToCustom HorizontalRule = Lua.callFunc "HorizontalRule"
blockToCustom (Header level attr inlines) =
- callFunc "Header" level (Stringify inlines) (attrToMap attr)
+ Lua.callFunc "Header" level (Stringify inlines) (attrToMap attr)
blockToCustom (CodeBlock attr str) =
- callFunc "CodeBlock" str (attrToMap attr)
+ Lua.callFunc "CodeBlock" str (attrToMap attr)
-blockToCustom (BlockQuote blocks) = callFunc "BlockQuote" (Stringify blocks)
+blockToCustom (BlockQuote blocks) =
+ Lua.callFunc "BlockQuote" (Stringify blocks)
blockToCustom (Table capt aligns widths headers rows) =
let aligns' = map show aligns
capt' = Stringify capt
headers' = map Stringify headers
rows' = map (map Stringify) rows
- in callFunc "Table" capt' aligns' widths headers' rows'
+ in Lua.callFunc "Table" capt' aligns' widths headers' rows'
-blockToCustom (BulletList items) = callFunc "BulletList" (map Stringify items)
+blockToCustom (BulletList items) =
+ Lua.callFunc "BulletList" (map Stringify items)
blockToCustom (OrderedList (num,sty,delim) items) =
- callFunc "OrderedList" (map Stringify items) num (show sty) (show delim)
+ Lua.callFunc "OrderedList" (map Stringify items) num (show sty) (show delim)
blockToCustom (DefinitionList items) =
- callFunc "DefinitionList"
- (map (KeyValue . (Stringify *** map Stringify)) items)
+ Lua.callFunc "DefinitionList"
+ (map (KeyValue . (Stringify *** map Stringify)) items)
blockToCustom (Div attr items) =
- callFunc "Div" (Stringify items) (attrToMap attr)
+ Lua.callFunc "Div" (Stringify items) (attrToMap attr)
-- | Convert list of Pandoc block elements to Custom.
blockListToCustom :: [Block] -- ^ List of block elements
-> Lua String
blockListToCustom xs = do
- blocksep <- callFunc "Blocksep"
+ blocksep <- Lua.callFunc "Blocksep"
bs <- mapM blockToCustom xs
return $ mconcat $ intersperse blocksep bs
@@ -200,51 +205,51 @@ inlineListToCustom lst = do
-- | Convert Pandoc inline element to Custom.
inlineToCustom :: Inline -> Lua String
-inlineToCustom (Str str) = callFunc "Str" str
+inlineToCustom (Str str) = Lua.callFunc "Str" str
-inlineToCustom Space = callFunc "Space"
+inlineToCustom Space = Lua.callFunc "Space"
-inlineToCustom SoftBreak = callFunc "SoftBreak"
+inlineToCustom SoftBreak = Lua.callFunc "SoftBreak"
-inlineToCustom (Emph lst) = callFunc "Emph" (Stringify lst)
+inlineToCustom (Emph lst) = Lua.callFunc "Emph" (Stringify lst)
-inlineToCustom (Strong lst) = callFunc "Strong" (Stringify lst)
+inlineToCustom (Strong lst) = Lua.callFunc "Strong" (Stringify lst)
-inlineToCustom (Strikeout lst) = callFunc "Strikeout" (Stringify lst)
+inlineToCustom (Strikeout lst) = Lua.callFunc "Strikeout" (Stringify lst)
-inlineToCustom (Superscript lst) = callFunc "Superscript" (Stringify lst)
+inlineToCustom (Superscript lst) = Lua.callFunc "Superscript" (Stringify lst)
-inlineToCustom (Subscript lst) = callFunc "Subscript" (Stringify lst)
+inlineToCustom (Subscript lst) = Lua.callFunc "Subscript" (Stringify lst)
-inlineToCustom (SmallCaps lst) = callFunc "SmallCaps" (Stringify lst)
+inlineToCustom (SmallCaps lst) = Lua.callFunc "SmallCaps" (Stringify lst)
-inlineToCustom (Quoted SingleQuote lst) = callFunc "SingleQuoted" (Stringify lst)
+inlineToCustom (Quoted SingleQuote lst) = Lua.callFunc "SingleQuoted" (Stringify lst)
-inlineToCustom (Quoted DoubleQuote lst) = callFunc "DoubleQuoted" (Stringify lst)
+inlineToCustom (Quoted DoubleQuote lst) = Lua.callFunc "DoubleQuoted" (Stringify lst)
-inlineToCustom (Cite cs lst) = callFunc "Cite" (Stringify lst) (map Stringify cs)
+inlineToCustom (Cite cs lst) = Lua.callFunc "Cite" (Stringify lst) (map Stringify cs)
inlineToCustom (Code attr str) =
- callFunc "Code" str (attrToMap attr)
+ Lua.callFunc "Code" str (attrToMap attr)
inlineToCustom (Math DisplayMath str) =
- callFunc "DisplayMath" str
+ Lua.callFunc "DisplayMath" str
inlineToCustom (Math InlineMath str) =
- callFunc "InlineMath" str
+ Lua.callFunc "InlineMath" str
inlineToCustom (RawInline format str) =
- callFunc "RawInline" (Stringify format) str
+ Lua.callFunc "RawInline" (Stringify format) str
-inlineToCustom LineBreak = callFunc "LineBreak"
+inlineToCustom LineBreak = Lua.callFunc "LineBreak"
inlineToCustom (Link attr txt (src,tit)) =
- callFunc "Link" (Stringify txt) src tit (attrToMap attr)
+ Lua.callFunc "Link" (Stringify txt) src tit (attrToMap attr)
inlineToCustom (Image attr alt (src,tit)) =
- callFunc "Image" (Stringify alt) src tit (attrToMap attr)
+ Lua.callFunc "Image" (Stringify alt) src tit (attrToMap attr)
-inlineToCustom (Note contents) = callFunc "Note" (Stringify contents)
+inlineToCustom (Note contents) = Lua.callFunc "Note" (Stringify contents)
inlineToCustom (Span attr items) =
- callFunc "Span" (Stringify items) (attrToMap attr)
+ Lua.callFunc "Span" (Stringify items) (attrToMap attr)