Custom writer: Raise PandocLuaException instead of using 'error'.

Eventually we'll change the return type so that no exception
is involved, but at least this can be trapped.
This commit is contained in:
John MacFarlane 2015-01-18 22:04:42 -08:00
parent ab8b00ea0c
commit 030d3b597d

View file

@ -1,5 +1,5 @@
{-# LANGUAGE OverlappingInstances, FlexibleInstances, OverloadedStrings,
ScopedTypeVariables #-}
ScopedTypeVariables, DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- Copyright (C) 2012-2014 John MacFarlane <jgm@berkeley.edu>
@ -35,6 +35,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options
import Data.List ( intersperse )
import Data.Char ( toLower )
import Data.Typeable
import Scripting.Lua (LuaState, StackValue, callfunc)
import Text.Pandoc.Writers.Shared
import qualified Scripting.Lua as Lua
@ -43,6 +44,7 @@ import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Data.Monoid
import Control.Monad (when)
import Control.Exception
import qualified Data.Map as M
import Text.Pandoc.Templates
@ -146,6 +148,11 @@ instance StackValue Citation where
peek = undefined
valuetype _ = Lua.TTABLE
data PandocLuaException = PandocLuaException String
deriving (Show, Typeable)
instance Exception PandocLuaException
-- | Convert Pandoc to custom markup.
writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String
writeCustom luaFile opts doc@(Pandoc meta _) = do
@ -156,7 +163,7 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do
-- check for error in lua script (later we'll change the return type
-- to handle this more gracefully):
when (status /= 0) $
Lua.tostring lua 1 >>= error
Lua.tostring lua 1 >>= throw . PandocLuaException
Lua.call lua 0 0
-- TODO - call hierarchicalize, so we have that info
rendered <- docToCustom lua opts doc