{-# LANGUAGE RankNTypes #-} -- | Module to generate SVGs from shapefiles. module GIS.Graphics.PlotSVG ( fileOptions , mkMapSVG , makeLensMapSVG ) where import GIS.Graphics.Plot import GIS.Graphics.Types hiding (title) import GIS.Types import Graphics.Rendering.Chart.Backend.Diagrams import Graphics.Rendering.Chart.Easy hiding (lens) -- | Default file options: PNG output and 1920x1080. To change the file size, -- you can do e.g. -- > fo_size .~ (640,480) $ fileOptions fileOptions :: FileOptions fileOptions = def { _fo_size = (1920, 1080) , _fo_format = SVG } -- | Given a `Map`, write it to file as an SVG. mkMapSVG :: FilePath -> Map -> IO () mkMapSVG path map' = renderableToFile fileOptions path (mkMapR map') >> putStrLn ("...output written to " <> path) makeLensMapSVG :: (Show a) => String -> FilePath -> Lens' District a -> [District] -> IO () makeLensMapSVG title filepath lens districts = renderableToFile fileOptions filepath (mkRenderableLens lens districts title) >> putStrLn ("...output written to " <> filepath)