-
-
Notifications
You must be signed in to change notification settings - Fork 3.4k
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
The module provides basic querying functions for image properties.
- Loading branch information
Showing
7 changed files
with
255 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
31 changes: 31 additions & 0 deletions
31
pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/ImageSize.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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) | ||
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,98 @@ | ||
{-# 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 @pandoc.image@ 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, 1, 13] | ||
, format `since` makeVersion [3, 1, 13] | ||
] | ||
|
||
-- | Find the size of an image. | ||
size :: DocumentedFunction PandocError | ||
size = defun "size" | ||
### liftPure2 (\img mwriterOpts -> imageSize (fromMaybe def mwriterOpts) img) | ||
<#> parameter peekByteString "string" "image" "image data" | ||
<#> opt (parameter peekWriterOptions "WriterOptions|table" "opts" | ||
"writer options") | ||
=#> functionResult (either (failLua . T.unpack) pushImageSize) "table" | ||
"image size information or error message" | ||
#? T.unlines | ||
[ "Returns a table containing the size and resolution of an image;" | ||
, "throws an error if the given string is not an image, or if the size" | ||
, "of the image cannot be determined." | ||
, "" | ||
, "The resulting table has four entires: *width*, *height*, *dpi\\_horz*," | ||
, "and *dpi\\_vert*." | ||
, "" | ||
, "The `opts` parameter, when given, should be either a WriterOptions" | ||
, "object such as `PANDOC_WRITER_OPTIONS`, or a table with a `dpi` entry." | ||
, "It affects the calculation for vector image formats such as SVG." | ||
] | ||
|
||
-- | Returns the format of an image. | ||
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 | ||
[ "Returns the format of an image as a lowercase string." | ||
, "" | ||
, "Formats recognized by pandoc include *png*, *gif*, *tiff*, *jpeg*," | ||
, "*pdf*, *svg*, *eps*, and *emf*." | ||
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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), | ||
}, | ||
} |