Skip to content

Commit

Permalink
Flip and rotate images in LaTeX output
Browse files Browse the repository at this point in the history
Ordinarily the LaTeX writer doesn't really need to get the bytes of the
images it's including, but we have to check them to get an EXIF
orientation. If the media fetch fails we're just punting and assuming a
default orientation.

It would be slightly dubious to bother doing this at all but LaTeX is
the default format for PDF output so it's worth making the effort.
  • Loading branch information
silby committed Nov 22, 2024
1 parent c5f0190 commit 76b03c1
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 7 deletions.
9 changes: 9 additions & 0 deletions src/Text/Pandoc/ImageSize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Text.Pandoc.ImageSize ( ImageType(..)
, Flip(..)
, Rotate(..)
, dimension
, rotateDirection
, lengthToDim
, scaleDimension
, inInch
Expand Down Expand Up @@ -515,3 +516,11 @@ imageTransform img =
exifToTransform 7 = def{tFlip = FlipH, tRotate = R90}
exifToTransform 8 = def{tRotate = R270}
exifToTransform _ = def

rotateDirection :: Rotate -> Direction -> Direction
rotateDirection R0 x = x
rotateDirection R90 Width = Height
rotateDirection R90 Height = Width
rotateDirection R180 x = x
rotateDirection R270 Width = Height
rotateDirection R270 Height = Width
33 changes: 26 additions & 7 deletions src/Text/Pandoc/Writers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ import Control.Monad
liftM,
when,
unless )
import Control.Monad.Except (catchError)
import Data.Containers.ListUtils (nubOrd)
import Data.Char (isDigit)
import Data.List (intersperse, (\\))
Expand All @@ -41,7 +42,7 @@ import qualified Data.Text as T
import Network.URI (unEscapeString)
import Text.DocTemplates (FromContext(lookupContext), renderTemplate)
import Text.Collate.Lang (renderLang, Lang(langLanguage))
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang, fetchItem)
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight,
styleToLaTeX)
Expand Down Expand Up @@ -1075,23 +1076,25 @@ inlineToLaTeX (Image attr@(_,_,kvs) _ (source, _)) = do
modify $ \s -> s{ stGraphics = True
, stSVG = stSVG s || isSVG }
opts <- gets stOptions
let showDim dir = let d = text (show dir) <> "="
in case dimension dir attr of
(ImageTransform flp rot) <- catchError ((imageTransform . fst) <$> fetchItem source) (\_ -> return def)
let redir = rotateDirection rot
showDim dir = let d = text (show dir) <> "="
in case dimension (redir dir) attr of
Just (Pixel a) ->
[d <> literal (showInInch opts (Pixel a)) <> "in"]
Just (Percent a) ->
[d <> literal (showFl (a / 100)) <>
case dir of
case (redir dir) of
Width -> "\\linewidth"
Height -> "\\textheight"
]
Just dim ->
[d <> text (show dim)]
Nothing ->
case dir of
Width | isJust (dimension Height attr) ->
Width | isJust (dimension (redir Height) attr) ->
[d <> "\\linewidth"]
Height | isJust (dimension Width attr) ->
Height | isJust (dimension (redir Width) attr) ->
[d <> "\\textheight"]
_ -> []
optList = showDim Width <> showDim Height <>
Expand All @@ -1107,14 +1110,30 @@ inlineToLaTeX (Image attr@(_,_,kvs) _ (source, _)) = do
source' = if isURI source
then source
else T.pack $ unEscapeString $ T.unpack source
-- For images in vertically-mirrored exif orientation, \scalebox{1}[-1]
-- will reflect them to below the baseline. It seems like to get the
-- final image to be aligned with the baseline again, we have to rotate
-- it 180 degrees from the default (baseline) origin and then rotate
-- it again about the center so it's facing right side up. In real life
-- where there's only 8 possible EXIF orientations, there's never any
-- other rotation required for a vertical flip, but I think it would
-- still interact correctly if it somehow came up.
flipbox NoFlip x = x
flipbox FlipH x = "\\scalebox{-1}[1]" <> braces x
flipbox FlipV x = "\\rotatebox[origin=c]{180}{\\rotatebox{180}{{\\scalebox{1}[-1]" <> braces x <> "}}}"
rotatebox R0 x = x
rotatebox R90 x = "\\rotatebox[origin=br]{-90}" <> braces x
rotatebox R180 x = "\\rotatebox[origin=c]{180}" <> braces x
rotatebox R270 x = "\\rotatebox[origin=bl]{-270}" <> braces x
source'' <- stringToLaTeX URLString source'
inHeading <- gets stInHeading
return $
(if inHeading then "\\protect" else "") <>
(case dimension Width attr `mplus` dimension Height attr of
Just _ -> id
Nothing -> ("\\pandocbounded" <>) . braces)
((if isSVG then "\\includesvg" else "\\includegraphics") <>
((rotatebox rot . flipbox flp) $
(if isSVG then "\\includesvg" else "\\includegraphics") <>
options <> braces (literal source''))
inlineToLaTeX (Note contents) = do
setEmptyLine False
Expand Down

0 comments on commit 76b03c1

Please sign in to comment.