Difference between revisions of "Library for PPM images"

From HaskellWiki
Jump to navigation Jump to search
m
m (Reverted edits by LonnieGaudette (Talk); changed back to last version by MathematicalOrchid)
 
(6 intermediate revisions by 2 users not shown)
Line 4: Line 4:
   
 
For those that don't know, PPM is probably the simplest possible image file format that other software will actually read! For example, [http://www.irfanview.com/ IrfanView] will read it. Thus, this is a simple, light-weight way to write programs that will output graphics files, using only pure Haskell 98 I/O.
 
For those that don't know, PPM is probably the simplest possible image file format that other software will actually read! For example, [http://www.irfanview.com/ IrfanView] will read it. Thus, this is a simple, light-weight way to write programs that will output graphics files, using only pure Haskell 98 I/O.
  +
 
The code is actually designed to work with my [[Library for colours]] - but you can supply something of your own if you prefer.
  +
  +
=== ASCII PPM ===
  +
  +
This is the 'P3' PPM format. The entire thing is plain ASCII. This makes it very easy to read and write, and extremely inefficient. Don't be surprised if a 800x800 pixel image takes up a couple of MB of space!
   
 
<haskell>
 
<haskell>
module PPM (write_ppm, save_ppm) where
+
module PPM (make_ppm, save_ppm) where
   
 
import Colour
 
import Colour
Line 29: Line 35:
 
</haskell>
 
</haskell>
   
  +
=== Binary PPM ===
The code is actually designed to work with my [[Library for colours]] - but you can supply something of your own if you prefer.
 
  +
  +
This is the 'P6' PPM format. The header is still plain ASCII, but the actual raster data is binary. This makes the file roughly 10x smaller. I suspect it also makes it go ''faster'' too. This library is a drop-in replacement for the one above; include whichever one you want depending on what output you want.
  +
  +
<haskell>
  +
module Fast_PPM (make_ppm, save_ppm) where
  +
  +
import Data.Word
  +
import qualified Data.ByteString as BIN
  +
import Colour
  +
  +
quant8 :: Double -> Word8
  +
quant8 x = floor $ x * 0xFF
  +
  +
cquant8 :: Colour -> [Word8]
  +
cquant8 (Colour r g b) = [quant8 r, quant8 g, quant8 b]
  +
  +
string_to_bin :: String -> BIN.ByteString
  +
string_to_bin = BIN.pack . map (fromIntegral . fromEnum)
  +
  +
header :: [[Colour]] -> BIN.ByteString
  +
header pss =
  +
let nx = length $ head pss
  +
ny = length pss
  +
in string_to_bin $ "P6\n" ++ show nx ++ " " ++ show ny ++ " 255\n"
  +
  +
body :: [[Colour]] -> BIN.ByteString
  +
body pss = BIN.pack $ concatMap (cquant8 . cclip) $ concat pss
  +
  +
make_ppm :: [[Colour]] -> BIN.ByteString
  +
make_ppm pss = BIN.append (header pss) (body pss)
  +
  +
save_ppm :: FilePath -> [[Colour]] -> IO ()
  +
save_ppm f pss = BIN.writeFile f (make_ppm pss)
  +
</haskell>
  +
  +
=== Binary PPM using Arrays ===
  +
  +
Coming soon. External interface looks something like this:
  +
  +
<haskell>
  +
module FrameBuffer where
  +
  +
import Colour
  +
  +
data FrameBuffer
  +
  +
make_fb :: (Int,Int) -> IO FrameBuffer
  +
  +
write_pixel :: FrameBuffer -> (Int,Int) -> Colour -> IO ()
  +
  +
save_ppm :: FrameBuffer -> FilePath -> IO ()
  +
</haskell>
  +
  +
Uses IOUArrays to drastically improve save speed. (And, in general, improves the efficiency of the rest of the program by 1) being more strict, and 2) using constant space for all drawing operations.)

Latest revision as of 21:05, 7 November 2011


Here's a trivial little thing I wrote for saving PPM images.

For those that don't know, PPM is probably the simplest possible image file format that other software will actually read! For example, IrfanView will read it. Thus, this is a simple, light-weight way to write programs that will output graphics files, using only pure Haskell 98 I/O.

The code is actually designed to work with my Library for colours - but you can supply something of your own if you prefer.

ASCII PPM

This is the 'P3' PPM format. The entire thing is plain ASCII. This makes it very easy to read and write, and extremely inefficient. Don't be surprised if a 800x800 pixel image takes up a couple of MB of space!

module PPM (make_ppm, save_ppm) where

import Colour

save_ppm :: FilePath -> [[Colour]] -> IO ()
save_ppm f css = writeFile f $ make_ppm css

make_ppm :: [[Colour]] -> String
make_ppm css =
  "P3\n" ++ (show $ length $ head css) ++ " " ++ (show $ length css) ++ " 255\n" ++
  (unlines $ map unwords $ group 15 $ map show $ concatMap colour $ concat css)

group _ [] = []
group n xs =
  let (xs0,xs1) = splitAt n xs
  in  xs0 : group n xs1

colour (Colour r g b) = [channel r, channel g, channel b]

channel :: Double -> Int
channel = floor . (255*) . min 1 . max 0

Binary PPM

This is the 'P6' PPM format. The header is still plain ASCII, but the actual raster data is binary. This makes the file roughly 10x smaller. I suspect it also makes it go faster too. This library is a drop-in replacement for the one above; include whichever one you want depending on what output you want.

module Fast_PPM (make_ppm, save_ppm) where

import Data.Word
import qualified Data.ByteString as BIN
import Colour

quant8 :: Double -> Word8
quant8 x = floor $ x * 0xFF

cquant8 :: Colour -> [Word8]
cquant8 (Colour r g b) = [quant8 r, quant8 g, quant8 b]

string_to_bin :: String -> BIN.ByteString
string_to_bin = BIN.pack . map (fromIntegral . fromEnum)

header :: [[Colour]] -> BIN.ByteString
header pss =
  let nx = length $ head pss
      ny = length        pss
  in  string_to_bin $ "P6\n" ++ show nx ++ " " ++ show ny ++ " 255\n"

body :: [[Colour]] -> BIN.ByteString
body pss = BIN.pack $ concatMap (cquant8 . cclip) $ concat pss

make_ppm :: [[Colour]] -> BIN.ByteString
make_ppm pss = BIN.append (header pss) (body pss)

save_ppm :: FilePath -> [[Colour]] -> IO ()
save_ppm f pss = BIN.writeFile f (make_ppm pss)

Binary PPM using Arrays

Coming soon. External interface looks something like this:

module FrameBuffer where

import Colour

data FrameBuffer

make_fb :: (Int,Int) -> IO FrameBuffer

write_pixel :: FrameBuffer -> (Int,Int) -> Colour -> IO ()

save_ppm :: FrameBuffer -> FilePath -> IO ()

Uses IOUArrays to drastically improve save speed. (And, in general, improves the efficiency of the rest of the program by 1) being more strict, and 2) using constant space for all drawing operations.)