Skip to content

Commit

Permalink
Lua: add new module pandoc.image
Browse files Browse the repository at this point in the history
The module provides basic querying functions for image properties.
  • Loading branch information
tarleb committed Jan 17, 2024
1 parent e5804af commit 5a220ea
Show file tree
Hide file tree
Showing 6 changed files with 195 additions and 0 deletions.
2 changes: 2 additions & 0 deletions pandoc-lua-engine/pandoc-lua-engine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@ library
, Text.Pandoc.Lua.Marshal.CommonState
, Text.Pandoc.Lua.Marshal.Context
, Text.Pandoc.Lua.Marshal.Format
, Text.Pandoc.Lua.Marshal.ImageSize
, Text.Pandoc.Lua.Marshal.PandocError
, Text.Pandoc.Lua.Marshal.ReaderOptions
, Text.Pandoc.Lua.Marshal.Reference
Expand All @@ -82,6 +83,7 @@ library
, Text.Pandoc.Lua.Marshal.WriterOptions
, Text.Pandoc.Lua.Module.CLI
, Text.Pandoc.Lua.Module.Format
, Text.Pandoc.Lua.Module.Image
, Text.Pandoc.Lua.Module.JSON
, Text.Pandoc.Lua.Module.MediaBag
, Text.Pandoc.Lua.Module.Pandoc
Expand Down
2 changes: 2 additions & 0 deletions pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ import qualified HsLua.Module.Path as Module.Path
import qualified HsLua.Module.Zip as Module.Zip
import qualified Text.Pandoc.Lua.Module.CLI as Pandoc.CLI
import qualified Text.Pandoc.Lua.Module.Format as Pandoc.Format
import qualified Text.Pandoc.Lua.Module.Image as Pandoc.Image
import qualified Text.Pandoc.Lua.Module.JSON as Pandoc.JSON
import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag
import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc
Expand Down Expand Up @@ -91,6 +92,7 @@ loadedModules :: [Module PandocError]
loadedModules =
[ Pandoc.CLI.documentedModule
, Pandoc.Format.documentedModule
, Pandoc.Image.documentedModule
, Pandoc.JSON.documentedModule
, Pandoc.MediaBag.documentedModule
, Pandoc.Scaffolding.documentedModule
Expand Down
31 changes: 31 additions & 0 deletions pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ImageSize.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Marshal.ImageSize
Copyright : © 2024 Albert Krewinkel
License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
Marshaling image properties.
-}
module Text.Pandoc.Lua.Marshal.ImageSize
( pushImageType
, pushImageSize
) where

import Data.Char (toLower)
import HsLua
import Text.Pandoc.ImageSize

-- | Pushes an 'ImageType' as a string value.
pushImageType :: LuaError e => Pusher e ImageType
pushImageType = pushString . map toLower . show

-- | Pushes a dimensional value.
pushImageSize :: LuaError e => Pusher e ImageSize
pushImageSize = pushAsTable
[ ("width", pushIntegral . pxX)
, ("height", pushIntegral . pxY)
, ("dpi_horz", pushIntegral . dpiX)
, ("dpi_vert", pushIntegral . dpiY)
]
99 changes: 99 additions & 0 deletions pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,99 @@
{-# LANGUAGE OverloadedStrings #-}
{-|
Module : Text.Pandoc.Lua.Module.Image
Copyright : © 2024 Albert Krewinkel
License : MIT
Maintainer : Albert Krewinkel <[email protected]>
Lua module for basic image operations.
-}
module Text.Pandoc.Lua.Module.Image (
-- * Module
documentedModule

-- ** Functions
, size
, format
)
where

import Prelude hiding (null)
import Data.Default (Default (def))
import Data.Maybe (fromMaybe)
import Data.Version (makeVersion)
import HsLua.Core
import HsLua.Marshalling
import HsLua.Packaging
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.ImageSize (imageType, imageSize)
import Text.Pandoc.Lua.PandocLua ()
import Text.Pandoc.Lua.Marshal.ImageSize (pushImageType, pushImageSize)
import Text.Pandoc.Lua.Marshal.WriterOptions (peekWriterOptions)

import qualified Data.Text as T

-- | The @aeson@ module specification.
documentedModule :: Module PandocError
documentedModule = Module
{ moduleName = "pandoc.image"
, moduleDescription = "Basic image querying functions."
, moduleFields = fields
, moduleFunctions = functions
, moduleOperations = []
, moduleTypeInitializers = []
}

--
-- Fields
--

-- | Exported fields.
fields :: LuaError e => [Field e]
fields = []

--
-- Functions
--

functions :: [DocumentedFunction PandocError]
functions =
[ size `since` makeVersion [3, 2, 0]
, format `since` makeVersion [3, 2, 0]
]

-- | Decode a JSON string into a Lua object.
size :: DocumentedFunction PandocError
size = defun "size"
### liftPure2
(\img mwriterOpts -> imageSize (fromMaybe def mwriterOpts) img)
<#> parameter peekByteString "string" "image" "image data"
<#> opt (parameter peekWriterOptions "WriterOptions" "writer_options"
"writer options")
=#> functionResult (either (failLua . T.unpack) pushImageSize) "string|table"
"image size object or error message"
-- #? T.unlines
-- [ "Creates a Lua object from a JSON string. The function returns an"
-- , "[[Inline]], [[Block]], [[Pandoc]], [[Inlines]], or [[Blocks]] element"
-- , "if the input can be decoded into represent any of those types."
-- , "Otherwise the default decoding is applied, using tables, booleans,"
-- , "numbers, and [null](#pandoc.json.null) to represent the JSON value."
-- , ""
-- , "The special handling of AST elements can be disabled by setting"
-- , "`pandoc_types` to `false`."
-- ]

-- | Encode a Lua object as JSON.
format :: LuaError e => DocumentedFunction e
format = defun "format"
### liftPure imageType
<#> parameter peekByteString "string" "image" "binary image data"
=#> functionResult (maybe pushnil pushImageType) "string|nil"
"image format, or nil if the format cannot be determined"
-- #? T.unlines
-- ["Encodes a Lua object as JSON string."
-- , ""
-- , "If the object has a metamethod with name `__tojson`, then the"
-- , "result is that of a call to that method with `object` passed as"
-- , "the sole argument. The result of that call is expected to be a"
-- , "valid JSON string, but this not checked."
-- ]
2 changes: 2 additions & 0 deletions pandoc-lua-engine/test/Tests/Lua/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,8 @@ tests =
("lua" </> "module" </> "pandoc-list.lua")
, testPandocLua "pandoc.format"
("lua" </> "module" </> "pandoc-format.lua")
, testPandocLua "pandoc.image"
("lua" </> "module" </> "pandoc-image.lua")
, testPandocLua "pandoc.json"
("lua" </> "module" </> "pandoc-json.lua")
, testPandocLua "pandoc.mediabag"
Expand Down
59 changes: 59 additions & 0 deletions pandoc-lua-engine/test/lua/module/pandoc-image.lua
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
--
-- Tests for the system module
--
local image = require 'pandoc.image'
local tasty = require 'tasty'

local group = tasty.test_group
local test = tasty.test_case
local assert = tasty.assert

local svg_image = [==[<?xml version="1.0"?>
<svg xmlns="http://www.w3.org/2000/svg"
xmlns:xlink="http://www.w3.org/1999/xlink"
height="70" width="70"
viewBox="-35 -35 70 70">
<title>test</title>
<!-- document shape -->
<polygon points="-10,-31.53 -10,-3.25 0,0 10,-3.25 10,-23.53 2,-31.53" />
</svg>
]==]

return {
-- Check existence of static fields
group 'static fields' {
},

group 'size' {
test('string', function ()
local imgsize = {
width = 70,
height = 70,
dpi_horz = 96,
dpi_vert = 96,
}
assert.are_same(image.size(svg_image), imgsize)
end),
test('fails on faulty eps', function ()
assert.error_matches(
function () image.size('%!PS EPSF') end,
'could not determine EPS size'
)
end),
test('fails if input is not an image', function ()
assert.error_matches(
function () image.size('not an image') end,
'could not determine image type'
)
end),
},

group 'format' {
test('SVG', function ()
assert.are_equal(image.format(svg_image), 'svg')
end),
test('returns nil if input is not an image', function ()
assert.is_nil(image.format('not an image'))
end),
},
}

0 comments on commit 5a220ea

Please sign in to comment.