{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Reanimate.LaTeX
( latexCfg,
TexEngine (..),
TexConfig (..),
latex,
latexWithHeaders,
latexChunks,
latexCfgChunks,
latexCfgChunksTrans,
mathChunks,
xelatex,
xelatexWithHeaders,
ctex,
ctexWithHeaders,
latexAlign,
chalkduster,
calligra,
noto,
helvet,
libertine,
biolinum,
droidSerif,
droidSans,
)
where
import Control.Lens ((&), (.~))
import Control.Monad.State (runState, state)
import qualified Data.ByteString as B
import Data.Foldable (Foldable (fold))
import Data.Hashable (Hashable)
import Data.Monoid (Last (Last))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import GHC.Generics (Generic)
import Graphics.SvgTree (Tree, clipPathRef, clipRule, mapTree, parseSvgFile,
pattern ClipPathTree, pattern None, strokeColor)
import Reanimate.Animation (SVG)
import Reanimate.Cache (cacheDiskSvg, cacheMem)
import Reanimate.External (zipArchive)
import Reanimate.Misc (requireExecutable, runCmd, withTempDir, withTempFile)
import Reanimate.Parameters (pNoExternals)
import Reanimate.Svg
import System.FilePath (replaceExtension, takeFileName, (</>))
import System.IO.Unsafe (unsafePerformIO)
data TexEngine = LaTeX | XeLaTeX | LuaLaTeX
deriving ((forall x. TexEngine -> Rep TexEngine x)
-> (forall x. Rep TexEngine x -> TexEngine) -> Generic TexEngine
forall x. Rep TexEngine x -> TexEngine
forall x. TexEngine -> Rep TexEngine x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TexEngine x -> TexEngine
$cfrom :: forall x. TexEngine -> Rep TexEngine x
Generic, Int -> TexEngine -> Int
TexEngine -> Int
(Int -> TexEngine -> Int)
-> (TexEngine -> Int) -> Hashable TexEngine
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TexEngine -> Int
$chash :: TexEngine -> Int
hashWithSalt :: Int -> TexEngine -> Int
$chashWithSalt :: Int -> TexEngine -> Int
Hashable, TexEngine -> TexEngine -> Bool
(TexEngine -> TexEngine -> Bool)
-> (TexEngine -> TexEngine -> Bool) -> Eq TexEngine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TexEngine -> TexEngine -> Bool
$c/= :: TexEngine -> TexEngine -> Bool
== :: TexEngine -> TexEngine -> Bool
$c== :: TexEngine -> TexEngine -> Bool
Eq, Eq TexEngine
Eq TexEngine
-> (TexEngine -> TexEngine -> Ordering)
-> (TexEngine -> TexEngine -> Bool)
-> (TexEngine -> TexEngine -> Bool)
-> (TexEngine -> TexEngine -> Bool)
-> (TexEngine -> TexEngine -> Bool)
-> (TexEngine -> TexEngine -> TexEngine)
-> (TexEngine -> TexEngine -> TexEngine)
-> Ord TexEngine
TexEngine -> TexEngine -> Bool
TexEngine -> TexEngine -> Ordering
TexEngine -> TexEngine -> TexEngine
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TexEngine -> TexEngine -> TexEngine
$cmin :: TexEngine -> TexEngine -> TexEngine
max :: TexEngine -> TexEngine -> TexEngine
$cmax :: TexEngine -> TexEngine -> TexEngine
>= :: TexEngine -> TexEngine -> Bool
$c>= :: TexEngine -> TexEngine -> Bool
> :: TexEngine -> TexEngine -> Bool
$c> :: TexEngine -> TexEngine -> Bool
<= :: TexEngine -> TexEngine -> Bool
$c<= :: TexEngine -> TexEngine -> Bool
< :: TexEngine -> TexEngine -> Bool
$c< :: TexEngine -> TexEngine -> Bool
compare :: TexEngine -> TexEngine -> Ordering
$ccompare :: TexEngine -> TexEngine -> Ordering
$cp1Ord :: Eq TexEngine
Ord, ReadPrec [TexEngine]
ReadPrec TexEngine
Int -> ReadS TexEngine
ReadS [TexEngine]
(Int -> ReadS TexEngine)
-> ReadS [TexEngine]
-> ReadPrec TexEngine
-> ReadPrec [TexEngine]
-> Read TexEngine
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TexEngine]
$creadListPrec :: ReadPrec [TexEngine]
readPrec :: ReadPrec TexEngine
$creadPrec :: ReadPrec TexEngine
readList :: ReadS [TexEngine]
$creadList :: ReadS [TexEngine]
readsPrec :: Int -> ReadS TexEngine
$creadsPrec :: Int -> ReadS TexEngine
Read, Int -> TexEngine -> ShowS
[TexEngine] -> ShowS
TexEngine -> String
(Int -> TexEngine -> ShowS)
-> (TexEngine -> String)
-> ([TexEngine] -> ShowS)
-> Show TexEngine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TexEngine] -> ShowS
$cshowList :: [TexEngine] -> ShowS
show :: TexEngine -> String
$cshow :: TexEngine -> String
showsPrec :: Int -> TexEngine -> ShowS
$cshowsPrec :: Int -> TexEngine -> ShowS
Show)
data TexConfig = TexConfig
{ TexConfig -> TexEngine
texConfigEngine :: TexEngine,
:: [T.Text],
TexConfig -> [Text]
texConfigPostScript :: [T.Text]
}
deriving ((forall x. TexConfig -> Rep TexConfig x)
-> (forall x. Rep TexConfig x -> TexConfig) -> Generic TexConfig
forall x. Rep TexConfig x -> TexConfig
forall x. TexConfig -> Rep TexConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TexConfig x -> TexConfig
$cfrom :: forall x. TexConfig -> Rep TexConfig x
Generic, Int -> TexConfig -> Int
TexConfig -> Int
(Int -> TexConfig -> Int)
-> (TexConfig -> Int) -> Hashable TexConfig
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TexConfig -> Int
$chash :: TexConfig -> Int
hashWithSalt :: Int -> TexConfig -> Int
$chashWithSalt :: Int -> TexConfig -> Int
Hashable, ReadPrec [TexConfig]
ReadPrec TexConfig
Int -> ReadS TexConfig
ReadS [TexConfig]
(Int -> ReadS TexConfig)
-> ReadS [TexConfig]
-> ReadPrec TexConfig
-> ReadPrec [TexConfig]
-> Read TexConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TexConfig]
$creadListPrec :: ReadPrec [TexConfig]
readPrec :: ReadPrec TexConfig
$creadPrec :: ReadPrec TexConfig
readList :: ReadS [TexConfig]
$creadList :: ReadS [TexConfig]
readsPrec :: Int -> ReadS TexConfig
$creadsPrec :: Int -> ReadS TexConfig
Read, Int -> TexConfig -> ShowS
[TexConfig] -> ShowS
TexConfig -> String
(Int -> TexConfig -> ShowS)
-> (TexConfig -> String)
-> ([TexConfig] -> ShowS)
-> Show TexConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TexConfig] -> ShowS
$cshowList :: [TexConfig] -> ShowS
show :: TexConfig -> String
$cshow :: TexConfig -> String
showsPrec :: Int -> TexConfig -> ShowS
$cshowsPrec :: Int -> TexConfig -> ShowS
Show, TexConfig -> TexConfig -> Bool
(TexConfig -> TexConfig -> Bool)
-> (TexConfig -> TexConfig -> Bool) -> Eq TexConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TexConfig -> TexConfig -> Bool
$c/= :: TexConfig -> TexConfig -> Bool
== :: TexConfig -> TexConfig -> Bool
$c== :: TexConfig -> TexConfig -> Bool
Eq, Eq TexConfig
Eq TexConfig
-> (TexConfig -> TexConfig -> Ordering)
-> (TexConfig -> TexConfig -> Bool)
-> (TexConfig -> TexConfig -> Bool)
-> (TexConfig -> TexConfig -> Bool)
-> (TexConfig -> TexConfig -> Bool)
-> (TexConfig -> TexConfig -> TexConfig)
-> (TexConfig -> TexConfig -> TexConfig)
-> Ord TexConfig
TexConfig -> TexConfig -> Bool
TexConfig -> TexConfig -> Ordering
TexConfig -> TexConfig -> TexConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TexConfig -> TexConfig -> TexConfig
$cmin :: TexConfig -> TexConfig -> TexConfig
max :: TexConfig -> TexConfig -> TexConfig
$cmax :: TexConfig -> TexConfig -> TexConfig
>= :: TexConfig -> TexConfig -> Bool
$c>= :: TexConfig -> TexConfig -> Bool
> :: TexConfig -> TexConfig -> Bool
$c> :: TexConfig -> TexConfig -> Bool
<= :: TexConfig -> TexConfig -> Bool
$c<= :: TexConfig -> TexConfig -> Bool
< :: TexConfig -> TexConfig -> Bool
$c< :: TexConfig -> TexConfig -> Bool
compare :: TexConfig -> TexConfig -> Ordering
$ccompare :: TexConfig -> TexConfig -> Ordering
$cp1Ord :: Eq TexConfig
Ord)
defaultTexConfig :: TexConfig
defaultTexConfig :: TexConfig
defaultTexConfig = TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig TexEngine
LaTeX [] []
latexCfg :: TexConfig -> T.Text -> SVG
latexCfg :: TexConfig -> Text -> SVG
latexCfg (TexConfig TexEngine
engine [Text]
headers [Text]
postscript) =
[Text] -> [Text] -> Text -> SVG
gen [Text]
postscript [Text]
headers
where
gen :: [Text] -> [Text] -> Text -> SVG
gen =
case TexEngine
engine of
TexEngine
LaTeX -> TexEngine
-> String -> String -> [String] -> [Text] -> [Text] -> Text -> SVG
someTexWithHeaders TexEngine
engine String
"latex" String
"dvi" []
TexEngine
XeLaTeX -> TexEngine
-> String -> String -> [String] -> [Text] -> [Text] -> Text -> SVG
someTexWithHeaders TexEngine
engine String
"xelatex" String
"xdv" [String
"-no-pdf"]
TexEngine
LuaLaTeX -> TexEngine
-> String -> String -> [String] -> [Text] -> [Text] -> Text -> SVG
someTexWithHeaders TexEngine
engine String
"lualatex" String
"pdf" []
latex :: T.Text -> Tree
latex :: Text -> SVG
latex = [Text] -> Text -> SVG
latexWithHeaders []
latexWithHeaders :: [T.Text] -> T.Text -> Tree
= TexEngine
-> String -> String -> [String] -> [Text] -> [Text] -> Text -> SVG
someTexWithHeaders TexEngine
LaTeX String
"latex" String
"dvi" [] []
someTexWithHeaders ::
TexEngine ->
String ->
String ->
[String] ->
[T.Text] ->
[T.Text] ->
T.Text ->
Tree
TexEngine
_engine String
_exec String
_dvi [String]
_args [Text]
_postscript [Text]
_headers Text
tex
| Bool
pNoExternals = Text -> SVG
mkText Text
tex
someTexWithHeaders TexEngine
engine String
exec String
dvi [String]
args [Text]
postscript [Text]
headers Text
tex =
(IO SVG -> SVG
forall a. IO a -> a
unsafePerformIO (IO SVG -> SVG) -> (Text -> IO SVG) -> Text -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text -> IO SVG) -> Text -> IO SVG
cacheMem ((Text -> IO SVG) -> Text -> IO SVG)
-> ((Text -> IO SVG) -> Text -> IO SVG)
-> (Text -> IO SVG)
-> Text
-> IO SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> IO SVG) -> Text -> IO SVG
cacheDiskSvg) (TexEngine -> String -> String -> [String] -> Text -> IO SVG
latexToSVG TexEngine
engine String
dvi String
exec [String]
args))
Text
script
where
script :: Text
script = String -> [String] -> [Text] -> Text -> Text
mkTexScript String
exec [String]
args [Text]
headers ([Text] -> Text
T.unlines ([Text]
postscript [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
tex]))
latexCfgChunksTrans :: Traversable t => TexConfig -> (T.Text -> T.Text) -> t T.Text -> t Tree
latexCfgChunksTrans :: TexConfig -> (Text -> Text) -> t Text -> t SVG
latexCfgChunksTrans TexConfig
_cfg Text -> Text
f t Text
chunks | Bool
pNoExternals = (Text -> SVG) -> t Text -> t SVG
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> SVG
mkText (Text -> SVG) -> (Text -> Text) -> Text -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
f) t Text
chunks
latexCfgChunksTrans TexConfig
cfg Text -> Text
f t Text
chunks = [(SVG -> SVG, DrawAttributes, SVG)] -> t SVG
forall t b. [(t -> SVG, b, t)] -> t SVG
worker ([(SVG -> SVG, DrawAttributes, SVG)] -> t SVG)
-> [(SVG -> SVG, DrawAttributes, SVG)] -> t SVG
forall a b. (a -> b) -> a -> b
$ SVG -> [(SVG -> SVG, DrawAttributes, SVG)]
svgGlyphs (SVG -> [(SVG -> SVG, DrawAttributes, SVG)])
-> SVG -> [(SVG -> SVG, DrawAttributes, SVG)]
forall a b. (a -> b) -> a -> b
$ Text -> SVG
tex (Text -> SVG) -> Text -> SVG
forall a b. (a -> b) -> a -> b
$ Text -> Text
f (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ t Text -> Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold t Text
chunks
where
tex :: Text -> SVG
tex = TexConfig -> Text -> SVG
latexCfg TexConfig
cfg
merge :: [(t -> SVG, b, t)] -> SVG
merge [(t -> SVG, b, t)]
lst = [SVG] -> SVG
mkGroup [t -> SVG
fmt t
svg | (t -> SVG
fmt, b
_, t
svg) <- [(t -> SVG, b, t)]
lst]
checkResult :: (p, [a]) -> p
checkResult (p
r, []) = p
r
checkResult (p
_, [a]
_) = String -> p
forall a. HasCallStack => String -> a
error String
"latex chunk mismatch"
worker :: [(t -> SVG, b, t)] -> t SVG
worker = (t SVG, [(t -> SVG, b, t)]) -> t SVG
forall p a. (p, [a]) -> p
checkResult ((t SVG, [(t -> SVG, b, t)]) -> t SVG)
-> ([(t -> SVG, b, t)] -> (t SVG, [(t -> SVG, b, t)]))
-> [(t -> SVG, b, t)]
-> t SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. State [(t -> SVG, b, t)] (t SVG)
-> [(t -> SVG, b, t)] -> (t SVG, [(t -> SVG, b, t)])
forall s a. State s a -> s -> (a, s)
runState ((Text -> StateT [(t -> SVG, b, t)] Identity SVG)
-> t Text -> State [(t -> SVG, b, t)] (t SVG)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (([(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)]))
-> StateT [(t -> SVG, b, t)] Identity SVG
forall s (m :: * -> *) a. MonadState s m => (s -> (a, s)) -> m a
state (([(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)]))
-> StateT [(t -> SVG, b, t)] Identity SVG)
-> (Text -> [(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)]))
-> Text
-> StateT [(t -> SVG, b, t)] Identity SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)])
forall t b. Text -> [(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)])
workerSingle) ((Text -> Text) -> t Text -> t Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
f t Text
chunks))
workerSingle :: Text -> [(t -> SVG, b, t)] -> (SVG, [(t -> SVG, b, t)])
workerSingle Text
x [(t -> SVG, b, t)]
everything =
let width :: Int
width = [(SVG -> SVG, DrawAttributes, SVG)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([(SVG -> SVG, DrawAttributes, SVG)] -> Int)
-> [(SVG -> SVG, DrawAttributes, SVG)] -> Int
forall a b. (a -> b) -> a -> b
$ SVG -> [(SVG -> SVG, DrawAttributes, SVG)]
svgGlyphs (Text -> SVG
tex Text
x)
([(t -> SVG, b, t)]
first, [(t -> SVG, b, t)]
rest) = Int
-> [(t -> SVG, b, t)] -> ([(t -> SVG, b, t)], [(t -> SVG, b, t)])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
width [(t -> SVG, b, t)]
everything
in ([(t -> SVG, b, t)] -> SVG
forall t b. [(t -> SVG, b, t)] -> SVG
merge [(t -> SVG, b, t)]
first, [(t -> SVG, b, t)]
rest)
mathChunks :: Traversable t => t T.Text -> t Tree
mathChunks :: t Text -> t SVG
mathChunks = TexConfig -> (Text -> Text) -> t Text -> t SVG
forall (t :: * -> *).
Traversable t =>
TexConfig -> (Text -> Text) -> t Text -> t SVG
latexCfgChunksTrans TexConfig
defaultTexConfig (\Text
s -> Text
"$" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"$")
latexCfgChunks :: Traversable t => TexConfig -> t T.Text -> t Tree
latexCfgChunks :: TexConfig -> t Text -> t SVG
latexCfgChunks TexConfig
cfg = TexConfig -> (Text -> Text) -> t Text -> t SVG
forall (t :: * -> *).
Traversable t =>
TexConfig -> (Text -> Text) -> t Text -> t SVG
latexCfgChunksTrans TexConfig
cfg Text -> Text
forall a. a -> a
id
latexChunks :: Traversable t => t T.Text -> t Tree
latexChunks :: t Text -> t SVG
latexChunks = TexConfig -> (Text -> Text) -> t Text -> t SVG
forall (t :: * -> *).
Traversable t =>
TexConfig -> (Text -> Text) -> t Text -> t SVG
latexCfgChunksTrans TexConfig
defaultTexConfig Text -> Text
forall a. a -> a
id
xelatex :: Text -> Tree
xelatex :: Text -> SVG
xelatex = [Text] -> Text -> SVG
xelatexWithHeaders []
xelatexWithHeaders :: [T.Text] -> T.Text -> Tree
= TexEngine
-> String -> String -> [String] -> [Text] -> [Text] -> Text -> SVG
someTexWithHeaders TexEngine
XeLaTeX String
"xelatex" String
"xdv" [String
"-no-pdf"] []
ctex :: T.Text -> Tree
ctex :: Text -> SVG
ctex = [Text] -> Text -> SVG
ctexWithHeaders []
ctexWithHeaders :: [T.Text] -> T.Text -> Tree
[Text]
headers = [Text] -> Text -> SVG
xelatexWithHeaders (Text
"\\usepackage[UTF8]{ctex}" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
headers)
latexAlign :: Text -> Tree
latexAlign :: Text -> SVG
latexAlign Text
tex = Text -> SVG
latex (Text -> SVG) -> Text -> SVG
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines [Text
"\\begin{align*}", Text
tex, Text
"\\end{align*}"]
postprocess :: Tree -> Tree
postprocess :: SVG -> SVG
postprocess =
SVG -> SVG
simplify
(SVG -> SVG) -> (SVG -> SVG) -> SVG -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVG -> SVG
lowerTransformations
(SVG -> SVG) -> (SVG -> SVG) -> SVG -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double -> SVG -> SVG
scaleXY Double
0.1 (-Double
0.1)
(SVG -> SVG) -> (SVG -> SVG) -> SVG -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVG -> SVG
removeClipPaths
(SVG -> SVG) -> (SVG -> SVG) -> SVG -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SVG -> SVG
lowerIds
(SVG -> SVG) -> (SVG -> SVG) -> SVG -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SVG -> SVG) -> SVG -> SVG
mapTree SVG -> SVG
forall b. HasDrawAttributes b => b -> b
clearDrawAttr
where
clearDrawAttr :: b -> b
clearDrawAttr b
t = b
t b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& (Last Texture -> Identity (Last Texture)) -> b -> Identity b
forall c. HasDrawAttributes c => Lens' c (Last Texture)
strokeColor ((Last Texture -> Identity (Last Texture)) -> b -> Identity b)
-> Last Texture -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Texture -> Last Texture
forall a. Maybe a -> Last a
Last Maybe Texture
forall a. Maybe a
Nothing
enginePostprocess :: TexEngine -> Tree -> Tree
enginePostprocess :: TexEngine -> SVG -> SVG
enginePostprocess TexEngine
LuaLaTeX SVG
svg = Double -> Double -> SVG -> SVG
translate Double
0 (SVG -> Double
svgHeight SVG
svg) SVG
svg
enginePostprocess TexEngine
_ SVG
svg = SVG
svg
removeClipPaths :: SVG -> SVG
removeClipPaths :: SVG -> SVG
removeClipPaths = (SVG -> SVG) -> SVG -> SVG
mapTree SVG -> SVG
worker
where
worker :: SVG -> SVG
worker ClipPathTree {} = SVG
None
worker SVG
t = SVG
t SVG -> (SVG -> SVG) -> SVG
forall a b. a -> (a -> b) -> b
& (Last FillRule -> Identity (Last FillRule)) -> SVG -> Identity SVG
forall c. HasDrawAttributes c => Lens' c (Last FillRule)
clipRule ((Last FillRule -> Identity (Last FillRule))
-> SVG -> Identity SVG)
-> Last FillRule -> SVG -> SVG
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe FillRule -> Last FillRule
forall a. Maybe a -> Last a
Last Maybe FillRule
forall a. Maybe a
Nothing SVG -> (SVG -> SVG) -> SVG
forall a b. a -> (a -> b) -> b
& (Last ElementRef -> Identity (Last ElementRef))
-> SVG -> Identity SVG
forall c. HasDrawAttributes c => Lens' c (Last ElementRef)
clipPathRef ((Last ElementRef -> Identity (Last ElementRef))
-> SVG -> Identity SVG)
-> Last ElementRef -> SVG -> SVG
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe ElementRef -> Last ElementRef
forall a. Maybe a -> Last a
Last Maybe ElementRef
forall a. Maybe a
Nothing
latexToSVG :: TexEngine -> String -> String -> [String] -> Text -> IO Tree
latexToSVG :: TexEngine -> String -> String -> [String] -> Text -> IO SVG
latexToSVG TexEngine
engine String
dviExt String
latexExec [String]
latexArgs Text
tex = do
String
latexBin <- String -> IO String
requireExecutable String
latexExec
(String -> IO SVG) -> IO SVG
forall a. (String -> IO a) -> IO a
withTempDir ((String -> IO SVG) -> IO SVG) -> (String -> IO SVG) -> IO SVG
forall a b. (a -> b) -> a -> b
$ \String
tmp_dir -> String -> (String -> IO SVG) -> IO SVG
forall a. String -> (String -> IO a) -> IO a
withTempFile String
"tex" ((String -> IO SVG) -> IO SVG) -> (String -> IO SVG) -> IO SVG
forall a b. (a -> b) -> a -> b
$ \String
tex_file ->
String -> (String -> IO SVG) -> IO SVG
forall a. String -> (String -> IO a) -> IO a
withTempFile String
"svg" ((String -> IO SVG) -> IO SVG) -> (String -> IO SVG) -> IO SVG
forall a b. (a -> b) -> a -> b
$ \String
svg_file -> do
let dvi_file :: String
dvi_file =
String
tmp_dir String -> ShowS
</> String -> ShowS
replaceExtension (ShowS
takeFileName String
tex_file) String
dviExt
String -> ByteString -> IO ()
B.writeFile String
tex_file (Text -> ByteString
T.encodeUtf8 Text
tex)
String -> [String] -> IO ()
runCmd
String
latexBin
( [String]
latexArgs
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"-interaction=nonstopmode",
String
"-halt-on-error",
String
"-output-directory=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tmp_dir,
String
tex_file
]
)
if String
dviExt String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"pdf"
then do
String
pdf2svg <- String -> IO String
requireExecutable String
"pdf2svg"
String -> [String] -> IO ()
runCmd
String
pdf2svg
[String
dvi_file, String
svg_file]
else do
String
dvisvgm <- String -> IO String
requireExecutable String
"dvisvgm"
String -> [String] -> IO ()
runCmd
String
dvisvgm
[ String
dvi_file,
String
"--precision=5",
String
"--exact",
String
"--no-fonts",
String
"--verbosity=0",
String
"-o",
String
svg_file
]
Text
svg_data <- String -> IO Text
T.readFile String
svg_file
case String -> Text -> Maybe Document
parseSvgFile String
svg_file Text
svg_data of
Maybe Document
Nothing -> String -> IO SVG
forall a. HasCallStack => String -> a
error String
"Malformed svg"
Just Document
svg ->
SVG -> IO SVG
forall (m :: * -> *) a. Monad m => a -> m a
return (SVG -> IO SVG) -> SVG -> IO SVG
forall a b. (a -> b) -> a -> b
$
TexEngine -> SVG -> SVG
enginePostprocess TexEngine
engine (SVG -> SVG) -> SVG -> SVG
forall a b. (a -> b) -> a -> b
$
SVG -> SVG
postprocess (SVG -> SVG) -> SVG -> SVG
forall a b. (a -> b) -> a -> b
$ Document -> SVG
unbox (Document -> SVG) -> Document -> SVG
forall a b. (a -> b) -> a -> b
$ Document -> Document
replaceUses Document
svg
mkTexScript :: String -> [String] -> [Text] -> Text -> Text
mkTexScript :: String -> [String] -> [Text] -> Text -> Text
mkTexScript String
latexExec [String]
latexArgs [Text]
texHeaders Text
tex =
[Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"% " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack ([String] -> String
unwords (String
latexExec String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
latexArgs)),
Text
"\\documentclass[preview]{standalone}",
Text
"\\usepackage{amsmath}",
Text
"\\usepackage{gensymb}"
]
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
texHeaders
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ Text
"\\usepackage[english]{babel}",
Text
"\\linespread{1}",
Text
"\\begin{document}",
Text
tex,
Text
"\\end{document}"
]
chalkduster :: TexConfig
chalkduster :: TexConfig
chalkduster =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
XeLaTeX,
texConfigHeaders :: [Text]
texConfigHeaders =
[ Text
"\\usepackage[no-math]{fontspec}",
Text
"\\setmainfont[Mapping=tex-text,Path={" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
chalkdusterFont Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/},Extension=.ttf]{Chalkduster}",
Text
"\\usepackage[defaultmathsizes]{mathastext}"
],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
where
chalkdusterFont :: Text
chalkdusterFont =
String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
String -> ShowS
zipArchive
String
"https://www.ffonts.net/Chalkduster.font.zip"
String
"Wplv4RjuFiI0hDQnAM5MVHl2evrZqWstRLdVAfBomCM="
calligra :: TexConfig
calligra :: TexConfig
calligra =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders = [Text
"\\usepackage{calligra}"],
texConfigPostScript :: [Text]
texConfigPostScript = [Text
"\\calligra"]
}
noto :: TexConfig
noto :: TexConfig
noto =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders = [Text
"\\usepackage{noto}"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
helvet :: TexConfig
helvet :: TexConfig
helvet =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders = [Text
"\\usepackage{helvet}"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
libertine :: TexConfig
libertine :: TexConfig
libertine =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders = [Text
"\\usepackage{libertine}"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
biolinum :: TexConfig
biolinum :: TexConfig
biolinum =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders =
[Text
"\\usepackage{libertine}"
,Text
"\\renewcommand{\\familydefault}{\\sfdefault}"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
droidSerif :: TexConfig
droidSerif :: TexConfig
droidSerif =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders =
[Text
"\\usepackage[default]{droidserif}"
,Text
"\\let\\varepsilon\\epsilon"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}
droidSans :: TexConfig
droidSans :: TexConfig
droidSans =
TexConfig :: TexEngine -> [Text] -> [Text] -> TexConfig
TexConfig
{ texConfigEngine :: TexEngine
texConfigEngine = TexEngine
LaTeX,
texConfigHeaders :: [Text]
texConfigHeaders =
[Text
"\\usepackage[default]{droidsans}"
,Text
"\\let\\varepsilon\\epsilon"],
texConfigPostScript :: [Text]
texConfigPostScript = []
}