diff options
author | schrieveslaach <schrieveslaach@online.de> | 2017-06-12 15:52:29 +0200 |
---|---|---|
committer | GitHub <noreply@github.com> | 2017-06-12 15:52:29 +0200 |
commit | 635f299b441e238ccd34e3ad61c5e36f0ca30067 (patch) | |
tree | 11cfc34402975bad208f9a48d075fe2ace959e70 /src/Text/Pandoc/Lua | |
parent | 181c56d4003aa83abed23b95a452c4890aa3797c (diff) | |
parent | 23f3c2d7b4796d1af742a74999ce67924bf2abb3 (diff) | |
download | pandoc-635f299b441e238ccd34e3ad61c5e36f0ca30067.tar.gz |
Merge branch 'master' into textcolor-support
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Compat.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/PandocModule.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/SharedInstances.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/StackInstances.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Util.hs | 8 |
5 files changed, 35 insertions, 38 deletions
diff --git a/src/Text/Pandoc/Lua/Compat.hs b/src/Text/Pandoc/Lua/Compat.hs index 998d8d032..3fc81a15c 100644 --- a/src/Text/Pandoc/Lua/Compat.hs +++ b/src/Text/Pandoc/Lua/Compat.hs @@ -28,13 +28,13 @@ Compatibility helpers for hslua -} module Text.Pandoc.Lua.Compat ( loadstring ) where -import Scripting.Lua ( LuaState ) +import Scripting.Lua (LuaState) import qualified Scripting.Lua as Lua -- | Interpret string as lua code and load into the lua environment. loadstring :: LuaState -> String -> String -> IO Int #if MIN_VERSION_hslua(0,5,0) -loadstring lua script _ = Lua.loadstring lua script +loadstring lua script _ = Lua.loadstring lua script #else loadstring lua script cn = Lua.loadstring lua script cn #endif diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs index 15f19f024..27c19d4f0 100644 --- a/src/Text/Pandoc/Lua/PandocModule.hs +++ b/src/Text/Pandoc/Lua/PandocModule.hs @@ -27,25 +27,24 @@ Pandoc module for lua. -} module Text.Pandoc.Lua.PandocModule ( pushPandocModule ) where -import Data.ByteString.Char8 ( unpack ) -import Data.Default ( Default(..) ) -import Scripting.Lua ( LuaState, call, push, pushhsfunction, rawset) -import Text.Pandoc.Class hiding ( readDataFile ) -import Text.Pandoc.Definition ( Pandoc ) -import Text.Pandoc.Lua.Compat ( loadstring ) +import Control.Monad (unless) +import Data.ByteString.Char8 (unpack) +import Data.Default (Default (..)) +import Data.Text (pack) +import Scripting.Lua (LuaState, call, push, pushhsfunction, rawset) +import Text.Pandoc.Class hiding (readDataFile) +import Text.Pandoc.Definition (Pandoc) +import Text.Pandoc.Lua.Compat (loadstring) import Text.Pandoc.Lua.StackInstances () -import Text.Pandoc.Readers ( Reader(..), getReader ) -import Text.Pandoc.Shared ( readDataFile ) +import Text.Pandoc.Readers (Reader (..), getReader) +import Text.Pandoc.Shared (readDataFile) -- | Push the "pandoc" on the lua stack. pushPandocModule :: LuaState -> IO () pushPandocModule lua = do script <- pandocModuleScript status <- loadstring lua script "pandoc.lua" - if (status /= 0) - then return () - else do - call lua 0 1 + unless (status /= 0) $ call lua 0 1 push lua "__read" pushhsfunction lua read_doc rawset lua (-3) @@ -57,13 +56,13 @@ pandocModuleScript = unpack <$> readDataFile Nothing "pandoc.lua" read_doc :: String -> String -> IO (Either String Pandoc) read_doc formatSpec content = do case getReader formatSpec of - Left s -> return $ Left s + Left s -> return $ Left s Right reader -> case reader of - StringReader r -> do - res <- runIO $ r def content + TextReader r -> do + res <- runIO $ r def (pack content) case res of - Left s -> return . Left $ show s + Left s -> return . Left $ show s Right pd -> return $ Right pd _ -> return $ Left "Only string formats are supported at the moment." diff --git a/src/Text/Pandoc/Lua/SharedInstances.hs b/src/Text/Pandoc/Lua/SharedInstances.hs index 3d2d29ebf..a5d4ba1e9 100644 --- a/src/Text/Pandoc/Lua/SharedInstances.hs +++ b/src/Text/Pandoc/Lua/SharedInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane <jgm@berkeley.edu> +Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu> 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify @@ -16,9 +16,9 @@ You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} -{-# LANGUAGE CPP #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE LambdaCase #-} #if !MIN_VERSION_base(4,8,0) {-# LANGUAGE OverlappingInstances #-} #endif @@ -36,8 +36,8 @@ Shared StackValue instances for pandoc and generic types. -} module Text.Pandoc.Lua.SharedInstances () where -import Scripting.Lua ( LTYPE(..), StackValue(..), newtable ) -import Text.Pandoc.Lua.Util ( addRawInt, addValue, getRawInt, keyValuePairs ) +import Scripting.Lua (LTYPE (..), StackValue (..), newtable) +import Text.Pandoc.Lua.Util (addRawInt, addValue, getRawInt, keyValuePairs) import qualified Data.Map as M import qualified Text.Pandoc.UTF8 as UTF8 @@ -112,5 +112,5 @@ instance (StackValue a, StackValue b) => StackValue (Either a b) where peek lua idx = peek lua idx >>= \case Just left -> return . Just $ Left left Nothing -> fmap Right <$> peek lua idx - valuetype (Left x) = valuetype x + valuetype (Left x) = valuetype x valuetype (Right x) = valuetype x diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index 03f6e06e2..d2e3f630a 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2015 John MacFarlane <jgm@berkeley.edu> +Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu> 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify @@ -17,11 +17,11 @@ along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.StackInstances - Copyright : © 2012-2016 John MacFarlane + Copyright : © 2012-2017 John MacFarlane © 2017 Albert Krewinkel License : GNU GPL, version 2 or above @@ -32,13 +32,13 @@ StackValue instances for pandoc types. -} module Text.Pandoc.Lua.StackInstances () where -import Control.Applicative ( (<|>) ) -import Scripting.Lua - ( LTYPE(..), LuaState, StackValue(..), ltype, newtable, objlen ) +import Control.Applicative ((<|>)) +import Scripting.Lua (LTYPE (..), LuaState, StackValue (..), ltype, newtable, + objlen) import Text.Pandoc.Definition import Text.Pandoc.Lua.SharedInstances () -import Text.Pandoc.Lua.Util ( addValue, getTable, pushViaConstructor ) -import Text.Pandoc.Shared ( safeRead ) +import Text.Pandoc.Lua.Util (addValue, getTable, pushViaConstructor) +import Text.Pandoc.Shared (safeRead) instance StackValue Pandoc where push lua (Pandoc meta blocks) = do diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index f0b87c231..0a704d027 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane <jgm@berkeley.edu> +Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu> 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify @@ -42,10 +42,8 @@ module Text.Pandoc.Lua.Util , pushViaConstructor ) where -import Scripting.Lua - ( LuaState, StackValue(..) - , call, getglobal2, gettable, next, pop, pushnil, rawgeti, rawseti, settable - ) +import Scripting.Lua (LuaState, StackValue (..), call, getglobal2, gettable, + next, pop, pushnil, rawgeti, rawseti, settable) -- | Adjust the stack index, assuming that @n@ new elements have been pushed on -- the stack. |