{-| Module : Graphics.Autom.Paint Description : For converting vector data into images. Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com This module is meant to convert grids from 'Graphics.Autom.NextNearest' into images that can be displayed or saved to file. -} module Graphics.Autom.Paint (toPictureColored, toPicture, toDynImage, toPNG) where import Prelude (Int, div, Bool(..), fmap, map, (*), (+), fromIntegral, not, Float, round, RealFrac) import Data.ByteString (pack) import Graphics.Gloss.Data.Picture (Picture, bitmapOfByteString) import Data.Monoid (mconcat) import Codec.Picture (Image(..), Pixel8, DynamicImage(..), savePngImage) import Data.Word (Word8) import qualified Data.Vector.Unboxed as VU (length, toList, Vector) import qualified Data.Vector.Storable as VS (fromList) import Graphics.Gloss.Data.Color (Color, makeColor, rgbaOfColor) import Data.Colour.RGBSpace.HSL (hsl) import Data.Colour.RGBSpace (channelRed, channelGreen, channelBlue) import GHC.IO (FilePath) import GHC.Types (IO) -- |Takes a hue value (/H/SL) and returns a Gloss 'Color' hue :: Float -> Color hue degrees = let rgb = hsl degrees 1 0.7 (red, green, blue) = (channelRed rgb, channelGreen rgb, channelBlue rgb) in makeColor red green blue 1.0 ratioToByte :: RealFrac a => a -> Word8 ratioToByte r = round (r * 255) :: Word8 -- |Meant to be used with an 'overlaidGrid', it converts an overlaid -- grid into a colored Picture, in which a there is a different color -- for each of the 32-bit values assigned to the grid points. However, -- points that are black (i.e., False) remain black. toPictureColored :: VU.Vector (Bool, Int) -- ^ overlaid grid -> Int -- ^ row width -> Float -- ^ starting hue in degrees for bit value 0 -> Float -- ^ hue step rate in degrees (cycles if necessary) -> Picture toPictureColored v w sHue rate = bitmapOfByteString w (VU.length v `div` w) d False where d = mconcat (map f (VU.toList v)) f (b, i) = if not b then pack [0, 0, 0, 0] else (\(r', g', b', _) -> pack [ ratioToByte r' , ratioToByte g' , ratioToByte b' , ratioToByte 1.0 ]) (rgbaOfColor (hue (sHue + (fromIntegral i) * rate))) -- |Converts a grid into a black and white Gloss Picture, usually to -- be displayed on screen toPicture :: VU.Vector Bool -- ^ one bit of data per pixel (i.e., white or black) -> Int -- ^ width of a row -> Picture toPicture v w = bitmapOfByteString w (VU.length v `div` w) d False where d = mconcat (map f (VU.toList v)) f b = if b then pack [255, 255, 255, 255] else pack [0, 0, 0, 0] -- |Converts a grid into a black and white JuicyPixels image, usually -- to be saved to a file toDynImage :: VU.Vector Bool -- ^ one bit of data per pixel (i.e., white or black) -> Int -- ^ width of a row -> DynamicImage toDynImage v w = ImageY8 (Image { imageWidth = w , imageHeight = VU.length v `div` w , imageData = d }) where d = VS.fromList (fmap f (VU.toList v)) f b = if b then (255 :: Pixel8) else (0 :: Pixel8) -- |An alias for 'savePngImage', which saves a JuicePixel image to a file toPNG :: GHC.IO.FilePath -> DynamicImage -> GHC.Types.IO () toPNG = savePngImage