Skip to content

Commit

Permalink
Typst writer: fix handling of pixel image dimensions.
Browse files Browse the repository at this point in the history
These are now converted to inches as in the LaTeX writer.

Closes #9945.
  • Loading branch information
jgm committed Jan 2, 2025
1 parent 01b5459 commit 968b0c1
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 12 deletions.
33 changes: 21 additions & 12 deletions src/Text/Pandoc/Writers/Typst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ module Text.Pandoc.Writers.Typst (
) where
import Text.Pandoc.Definition
import Text.Pandoc.Class ( PandocMonad)
import Text.Pandoc.ImageSize ( dimension, Dimension(Pixel), Direction(..),
showInInch )
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..), isEnabled,
CaptionPosition(..) )
import Data.Text (Text)
Expand Down Expand Up @@ -309,12 +311,13 @@ blockToTypst block =
$$ blankline
Figure (ident,_,_) (Caption _mbshort capt) blocks -> do
caption <- blocksToTypst capt
opts <- gets stOptions
contents <- case blocks of
-- don't need #box around block-level image
[Para [Image (_,_,kvs) _ (src, _)]]
-> pure $ mkImage False src kvs
[Plain [Image (_,_,kvs) _ (src, _)]]
-> pure $ mkImage False src kvs
[Para [Image attr _ (src, _)]]
-> pure $ mkImage opts False src attr
[Plain [Image attr _ (src, _)]]
-> pure $ mkImage opts False src attr
_ -> brackets <$> blocksToTypst blocks
let lab = toLabel FreestandingLabel ident
return $ "#figure(" <> nest 2 ((contents <> ",")
Expand Down Expand Up @@ -433,23 +436,29 @@ inlineToTypst inline =
(if inlines == [Str src]
then mempty
else nowrap $ brackets contents) <> endCode
Image (_,_,kvs) _inlines (src,_tit) -> pure $ mkImage True src kvs
Image attr _inlines (src,_tit) -> do
opts <- gets stOptions
pure $ mkImage opts True src attr
Note blocks -> do
contents <- blocksToTypst blocks
return $ "#footnote" <> brackets (chomp contents) <> endCode

-- see #9104; need box or image is treated as block-level
mkImage :: Bool -> Text -> [(Text, Text)] -> Doc Text
mkImage useBox src kvs
mkImage :: WriterOptions -> Bool -> Text -> Attr -> Doc Text
mkImage opts useBox src attr
| useBox = "#box" <> parens coreImage
| otherwise = coreImage
where
src' = T.pack $ unEscapeString $ T.unpack src -- #9389
toDimAttr k =
case lookup k kvs of
Just v -> ", " <> literal k <> ": " <> literal v
Nothing -> mempty
dimAttrs = mconcat $ map toDimAttr ["height", "width"]
showDim (Pixel a) = literal (showInInch opts (Pixel a) <> "in")
showDim dim = text (show dim)
dimAttrs =
(case dimension Height attr of
Nothing -> mempty
Just dim -> ", height: " <> showDim dim) <>
(case dimension Width attr of
Nothing -> mempty
Just dim -> ", width: " <> showDim dim)
isData = "data:" `T.isPrefixOf` src'
dataSvg = "<svg xmlns=\"http://www.w3.org/2000/svg\" xmlns:xlink=\"http://www.w3.org/1999/xlink\"><image xlink:href=\"" <> src' <> "\" /></svg>"
coreImage
Expand Down
28 changes: 28 additions & 0 deletions test/command/9945.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
```
% pandoc -t typst --dpi 300
![](image.jpg){width=300 height=300}
^D
#box(image("image.jpg", height: 1in, width: 1in))
```

```
% pandoc -t typst --dpi 600
![](image.jpg){width=300px height=300px}
^D
#box(image("image.jpg", height: 0.5in, width: 0.5in))
```

```
% pandoc -t typst --dpi 600
![](image.jpg){width=1in height=3cm}
^D
#box(image("image.jpg", height: 3cm, width: 1in))
```


```
% pandoc -t typst --dpi 600
![](image.jpg){.foo .bar baz=3}
^D
#box(image("image.jpg"))
```

0 comments on commit 968b0c1

Please sign in to comment.