module Graphics.Gnuplot.Terminal.SVG (
T, cons,
encoding,
) where
import qualified Graphics.Gnuplot.Private.Terminal as Terminal
import qualified Graphics.Gnuplot.Private.Encoding as Encoding
import Graphics.Gnuplot.Utility (quote, )
data T =
Cons {
T -> FilePath
filename_ :: FilePath,
T -> Maybe T
encoding_ :: Maybe Encoding.T
}
cons :: FilePath -> T
cons :: FilePath -> T
cons FilePath
path =
Cons :: FilePath -> Maybe T -> T
Cons {
filename_ :: FilePath
filename_ = FilePath
path,
encoding_ :: Maybe T
encoding_ = Maybe T
forall a. Maybe a
Nothing
}
encoding :: Encoding.T -> T -> T
encoding :: T -> T -> T
encoding T
enc T
term = T
term{encoding_ :: Maybe T
encoding_ = T -> Maybe T
forall a. a -> Maybe a
Just T
enc}
instance Terminal.C T where
canonical :: T -> T
canonical T
term =
Cons :: [FilePath] -> [FilePath] -> [FilePath] -> Bool -> T
Terminal.Cons {
precommands :: [FilePath]
Terminal.precommands = Maybe T -> [FilePath]
Encoding.formatMaybe (Maybe T -> [FilePath]) -> Maybe T -> [FilePath]
forall a b. (a -> b) -> a -> b
$ T -> Maybe T
encoding_ T
term,
options :: [FilePath]
Terminal.options =
FilePath
"svg" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:
[],
commands :: [FilePath]
Terminal.commands =
[FilePath
"set output " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath
quote (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ T -> FilePath
filename_ T
term)],
interactive :: Bool
Terminal.interactive = Bool
False
}