{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-}
module Text.Pandoc.Image ( svgToPng ) where
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
import Control.Monad.IO.Class (MonadIO(liftIO))
svgToPng :: MonadIO m
=> Int
-> L.ByteString
-> m (Either Text L.ByteString)
svgToPng :: forall (m :: * -> *).
MonadIO m =>
Int -> ByteString -> m (Either Text ByteString)
svgToPng Int
dpi ByteString
bs = do
let dpi' :: String
dpi' = forall a. Show a => a -> String
show Int
dpi
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
(do (ExitCode
exit, ByteString
out) <- Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess forall a. Maybe a
Nothing String
"rsvg-convert"
[String
"-f",String
"png",String
"-a",String
"--dpi-x",String
dpi',String
"--dpi-y",String
dpi']
ByteString
bs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if ExitCode
exit forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
then forall a b. b -> Either a b
Right ByteString
out
else forall a b. a -> Either a b
Left Text
"conversion from SVG failed")
(\(SomeException
e :: E.SomeException) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$
Text
"check that rsvg-convert is in path.\n" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow SomeException
e)