diff options
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Filter.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Global.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Init.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/CommonState.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/MediaBag.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Pandoc.hs | 19 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 18 |
8 files changed, 38 insertions, 32 deletions
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs index 9416bf41f..74c7058f3 100644 --- a/src/Text/Pandoc/Lua/Filter.hs +++ b/src/Text/Pandoc/Lua/Filter.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NoImplicitPrelude #-} {- | Module : Text.Pandoc.Lua.Filter @@ -180,7 +180,7 @@ constructorsFor :: DataType -> [String] constructorsFor x = map show (dataTypeConstrs x) inlineElementNames :: [String] -inlineElementNames = "Inline" : constructorsFor (dataTypeOf (Str [])) +inlineElementNames = "Inline" : constructorsFor (dataTypeOf (Str mempty)) blockElementNames :: [String] blockElementNames = "Block" : constructorsFor (dataTypeOf (Para [])) diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs index b9b6c9cd9..20963f831 100644 --- a/src/Text/Pandoc/Lua/Global.hs +++ b/src/Text/Pandoc/Lua/Global.hs @@ -27,11 +27,12 @@ import Text.Pandoc.Lua.Marshaling () import Text.Pandoc.Lua.Util (addFunction) import Text.Pandoc.Options (ReaderOptions) +import qualified Data.Text as Text import qualified Foreign.Lua as Lua -- | Permissible global Lua variables. data Global = - FORMAT String + FORMAT Text.Text | PANDOC_API_VERSION | PANDOC_DOCUMENT Pandoc | PANDOC_READER_OPTIONS ReaderOptions diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs index f1cab7e82..cf6c71231 100644 --- a/src/Text/Pandoc/Lua/Init.hs +++ b/src/Text/Pandoc/Lua/Init.hs @@ -28,13 +28,14 @@ import Text.Pandoc.Lua.Packages (LuaPackageParams (..), installPandocPackageSearcher) import Text.Pandoc.Lua.Util (loadScriptFromDataDir) +import qualified Data.Text as Text import qualified Foreign.Lua as Lua import qualified Foreign.Lua.Module.Text as Lua import qualified Text.Pandoc.Definition as Pandoc import qualified Text.Pandoc.Lua.Module.Pandoc as ModulePandoc -- | Lua error message -newtype LuaException = LuaException String deriving (Show) +newtype LuaException = LuaException Text.Text deriving (Show) -- | Run the lua interpreter, using pandoc's default way of environment -- initialization. @@ -56,7 +57,7 @@ runLua luaOp = do return (opResult, st) liftIO $ setForeignEncoding enc case res of - Left (Lua.Exception msg) -> return $ Left (LuaException msg) + Left (Lua.Exception msg) -> return $ Left (LuaException $ Text.pack msg) Right (x, newState) -> do putCommonState newState return $ Right x diff --git a/src/Text/Pandoc/Lua/Marshaling/CommonState.hs b/src/Text/Pandoc/Lua/Marshaling/CommonState.hs index eed1500ec..b65396f68 100644 --- a/src/Text/Pandoc/Lua/Marshaling/CommonState.hs +++ b/src/Text/Pandoc/Lua/Marshaling/CommonState.hs @@ -1,6 +1,7 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Lua.Marshaling.CommonState Copyright : © 2012-2019 John MacFarlane @@ -23,6 +24,7 @@ import Text.Pandoc.Logging (LogMessage, showLogMessage) import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..)) import qualified Data.Map as Map +import qualified Data.Text as Text import qualified Foreign.Lua as Lua import qualified Text.Pandoc.Lua.Util as LuaUtil @@ -46,7 +48,7 @@ indexCommonState st (AnyValue idx) = Lua.ltype idx >>= \case Lua.TypeString -> 1 <$ (Lua.peek idx >>= pushField) _ -> 1 <$ Lua.pushnil where - pushField :: String -> Lua () + pushField :: Text.Text -> Lua () pushField name = case lookup name commonStateFields of Just pushValue -> pushValue st Nothing -> Lua.pushnil @@ -71,7 +73,7 @@ pairsCommonState st = do (nextKey, pushValue):_ -> 2 <$ (Lua.push nextKey *> pushValue st) _ -> 2 <$ (Lua.pushnil *> Lua.pushnil) -commonStateFields :: [(String, CommonState -> Lua ())] +commonStateFields :: [(Text.Text, CommonState -> Lua ())] commonStateFields = [ ("input_files", Lua.push . stInputFiles) , ("output_file", Lua.push . Lua.Optional . stOutputFile) @@ -98,5 +100,5 @@ instance Pushable LogMessage where pushLogMessageMetatable = ensureUserdataMetatable logMessageTypeName $ LuaUtil.addFunction "__tostring" tostringLogMessage -tostringLogMessage :: LogMessage -> Lua String +tostringLogMessage :: LogMessage -> Lua Text.Text tostringLogMessage = return . showLogMessage diff --git a/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs b/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs index 5395f6fc8..226fe2e71 100644 --- a/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs +++ b/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs @@ -25,6 +25,7 @@ import Text.Pandoc.Lua.Marshaling.CommonState () import Text.Pandoc.Options (ReaderOptions (..), TrackChanges) import qualified Data.Set as Set +import qualified Data.Text as Text import qualified Foreign.Lua as Lua import qualified Text.Pandoc.Lua.Util as LuaUtil @@ -44,9 +45,9 @@ instance Pushable ReaderOptions where (standalone :: Bool) (columns :: Int) (tabStop :: Int) - (indentedCodeClasses :: [String]) - (abbreviations :: Set.Set String) - (defaultImageExtension :: String) + (indentedCodeClasses :: [Text.Text]) + (abbreviations :: Set.Set Text.Text) + (defaultImageExtension :: Text.Text) (trackChanges :: TrackChanges) (stripComments :: Bool) = ro diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs index 261785665..951571ddd 100644 --- a/src/Text/Pandoc/Lua/Module/MediaBag.hs +++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs @@ -15,7 +15,6 @@ module Text.Pandoc.Lua.Module.MediaBag import Prelude import Control.Monad (zipWithM_) -import Data.Maybe (fromMaybe) import Foreign.Lua (Lua, NumResults, Optional, liftIO) import Text.Pandoc.Class (CommonState (..), fetchItem, putCommonState, runIOorExplode, setMediaBag) @@ -25,6 +24,7 @@ import Text.Pandoc.Lua.Util (addFunction) import Text.Pandoc.MIME (MimeType) import qualified Data.ByteString.Lazy as BL +import qualified Data.Text as T import qualified Foreign.Lua as Lua import qualified Text.Pandoc.MediaBag as MB @@ -113,7 +113,7 @@ mediaDirectoryFn = do Lua.push "length" *> Lua.push contentLength *> Lua.rawset (-3) Lua.rawseti (-2) idx -fetch :: String +fetch :: T.Text -> Lua NumResults fetch src = do commonState <- getCommonState @@ -122,6 +122,6 @@ fetch src = do putCommonState commonState setMediaBag mediaBag fetchItem src - Lua.push $ fromMaybe "" mimeType + Lua.push $ maybe "" T.unpack mimeType Lua.push bs return 2 -- returns 2 values: contents, mimetype diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs index 182008da7..36d6f4009 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -1,5 +1,6 @@ -{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Lua.Module.Pandoc Copyright : Copyright © 2017-2019 Albert Krewinkel @@ -19,7 +20,6 @@ import Control.Monad (when) import Control.Monad.Except (throwError) import Data.Default (Default (..)) import Data.Maybe (fromMaybe) -import Data.Text (pack) import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable) import System.Exit (ExitCode (..)) import Text.Pandoc.Class (runIO) @@ -33,6 +33,7 @@ import Text.Pandoc.Readers (Reader (..), getReader) import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as BSL +import qualified Data.Text as T import qualified Foreign.Lua as Lua import qualified Text.Pandoc.Lua.Util as LuaUtil import Text.Pandoc.Error @@ -59,22 +60,22 @@ walkInline = walkElement walkBlock :: Block -> LuaFilter -> Lua Block walkBlock = walkElement -readDoc :: String -> Optional String -> Lua NumResults +readDoc :: T.Text -> Optional T.Text -> Lua NumResults readDoc content formatSpecOrNil = do let formatSpec = fromMaybe "markdown" (Lua.fromOptional formatSpecOrNil) res <- Lua.liftIO . runIO $ getReader formatSpec >>= \(rdr,es) -> case rdr of TextReader r -> - r def{ readerExtensions = es } (pack content) + r def{ readerExtensions = es } content _ -> throwError $ PandocSomeError $ "Only textual formats are supported" case res of Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc Left (PandocUnknownReaderError f) -> Lua.raiseError $ - "Unknown reader: " ++ f + "Unknown reader: " <> f Left (PandocUnsupportedExtensionError e f) -> Lua.raiseError $ - "Extension " ++ e ++ " not supported for " ++ f + "Extension " <> e <> " not supported for " <> f Left e -> Lua.raiseError $ show e -- | Pipes input through a command. @@ -86,10 +87,10 @@ pipeFn command args input = do (ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input case ec of ExitSuccess -> 1 <$ Lua.push output - ExitFailure n -> Lua.raiseError (PipeError command n output) + ExitFailure n -> Lua.raiseError (PipeError (T.pack command) n output) data PipeError = PipeError - { pipeErrorCommand :: String + { pipeErrorCommand :: T.Text , pipeErrorCode :: Int , pipeErrorOutput :: BL.ByteString } @@ -118,7 +119,7 @@ instance Pushable PipeError where pipeErrorMessage :: PipeError -> Lua BL.ByteString pipeErrorMessage (PipeError cmd errorCode output) = return $ mconcat [ BSL.pack "Error running " - , BSL.pack cmd + , BSL.pack $ T.unpack cmd , BSL.pack " (error code " , BSL.pack $ show errorCode , BSL.pack "): " diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index 057e6580b..7d6dd0fab 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -15,7 +15,6 @@ module Text.Pandoc.Lua.Module.Utils import Prelude import Control.Applicative ((<|>)) -import Data.Char (toLower) import Data.Default (def) import Data.Version (Version) import Foreign.Lua (Peekable, Lua, NumResults) @@ -27,6 +26,7 @@ import Text.Pandoc.Lua.Util (addFunction) import qualified Data.Digest.Pure.SHA as SHA import qualified Data.ByteString.Lazy as BSL +import qualified Data.Text as T import qualified Foreign.Lua as Lua import qualified Text.Pandoc.Builder as B import qualified Text.Pandoc.Filter.JSON as JSONFilter @@ -64,7 +64,7 @@ makeSections number baselevel = -- limit years to the range 1601-9999 (ISO 8601 accepts greater than -- or equal to 1583, but MS Word only accepts dates starting 1601). -- Returns nil instead of a string if the conversion failed. -normalizeDate :: String -> Lua (Lua.Optional String) +normalizeDate :: T.Text -> Lua (Lua.Optional T.Text) normalizeDate = return . Lua.Optional . Shared.normalizeDate -- | Run a JSON filter on the given document. @@ -88,13 +88,13 @@ runJSONFilter mbDatadir doc filterFile optArgs = do -- | Calculate the hash of the given contents. sha1 :: BSL.ByteString - -> Lua String -sha1 = return . SHA.showDigest . SHA.sha1 + -> Lua T.Text +sha1 = return . T.pack . SHA.showDigest . SHA.sha1 -- | Convert pandoc structure to a string with formatting removed. -- Footnotes are skipped (since we don't want their contents in link -- labels). -stringify :: AstElement -> Lua String +stringify :: AstElement -> Lua T.Text stringify el = return $ case el of PandocElement pd -> Shared.stringify pd InlineElement i -> Shared.stringify i @@ -102,11 +102,11 @@ stringify el = return $ case el of MetaElement m -> Shared.stringify m CitationElement c -> Shared.stringify c MetaValueElement m -> stringifyMetaValue m - _ -> "" + _ -> mempty -stringifyMetaValue :: MetaValue -> String +stringifyMetaValue :: MetaValue -> T.Text stringifyMetaValue mv = case mv of - MetaBool b -> map toLower (show b) + MetaBool b -> T.toLower $ T.pack (show b) MetaString s -> s _ -> Shared.stringify mv @@ -139,5 +139,5 @@ instance Peekable AstElement where "Expected an AST element, but could not parse value as such." -- | Convert a number < 4000 to uppercase roman numeral. -toRomanNumeral :: Lua.Integer -> Lua String +toRomanNumeral :: Lua.Integer -> Lua T.Text toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral |