Add Text.Pandoc.Image with unexported svgToPng.

This commit is contained in:
John MacFarlane 2020-02-12 21:37:42 -08:00
parent f5ea5f0aad
commit 3a181f0a97
2 changed files with 41 additions and 0 deletions

View file

@ -632,6 +632,7 @@ library
Text.Pandoc.UUID,
Text.Pandoc.Translations,
Text.Pandoc.Slides,
Text.Pandoc.Image,
Paths_pandoc
autogen-modules: Paths_pandoc
buildable: True

40
src/Text/Pandoc/Image.hs Normal file
View file

@ -0,0 +1,40 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-}
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Image
Copyright : Copyright (C) 2020 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
Portability : portable
Functions for converting images.
-}
module Text.Pandoc.Image ( svgToPng ) where
import Prelude
import Text.Pandoc.Options (WriterOptions(..))
import Text.Pandoc.Process (pipeProcess)
import qualified Data.ByteString.Lazy as L
import System.Exit
import Data.Text (Text)
import Text.Pandoc.Shared (tshow)
import qualified Control.Exception as E
-- | Convert svg image to png. rsvg-convert
-- is used and must be available on the path.
svgToPng :: WriterOptions
-> L.ByteString -- ^ Input image as bytestring
-> IO (Either Text L.ByteString)
svgToPng opts bs = do
let dpi = show $ writerDpi opts
E.catch
(do (exit, out) <- pipeProcess Nothing "rsvg-convert"
["-f","png","-a","--dpi-x",dpi,"--dpi-y",dpi]
bs
if exit == ExitSuccess
then return $ Right out
else return $ Left "conversion from SVG failed")
(\(e :: E.SomeException) -> return $ Left $
"check that rsvg-convert is in path.\n" <> tshow e)