{-# LANGUAGE RankNTypes #-} -- | Module to generate PNGs from shapefiles module GIS.Graphics.PlotPNG ( fileOptions , mkMap , mkLensMap , mkMapPng , makeLensMapPng ) where import Control.Lens hiding (lens) import GIS.Graphics.Plot import GIS.Graphics.PlotSVG hiding (fileOptions) import GIS.Graphics.Types hiding (title) import GIS.Types import GIS.Utils import Graphics.Rendering.Chart.Backend.Cairo import Graphics.Rendering.Chart.Easy hiding (lens) -- FIXME allow all for cairo -- | 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 = PNG } -- | Given a `Map` write it to file, where the format is determined by the -- extension. mkMap :: FilePath -> Map -> IO () mkMap filepath map' = case getExt filepath of "png" -> mkMapPng filepath map' "svg" -> mkMapSVG filepath map' _ -> error "file extension must be one of: .svg, .png" -- | Given a `Map` write it to file, where the format is determined by the -- extension. mkLensMap :: (Show a) => String -> FilePath -> Lens' District a -> [District] -> IO () mkLensMap title filepath lens districts = case getExt filepath of "png" -> makeLensMapPng title filepath lens districts "svg" -> makeLensMapSVG title filepath lens districts _ -> error "file extension must be one of: .svg, .png" -- | Given a `Map`, write it to file. mkMapPng :: FilePath -> Map -> IO () mkMapPng path map' = renderableToFile fileOptions path (mkMapR map') >> putStrLn ("...output written to " <> path) makeLensMapPng :: (Show a) => String -> FilePath -> Lens' District a -> [District] -> IO () makeLensMapPng title filepath lens districts = renderableToFile fileOptions filepath (mkRenderableLens lens districts title) >> putStrLn ("...output written to " <> filepath)