Library for PPM images

From HaskellWiki
Revision as of 15:51, 12 April 2007 by MathematicalOrchid (talk | contribs) (Simple PPM image saving.)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search


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.

module PPM (write_ppm, save_ppm) where

import Colour

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

write_ppm :: [[Colour]] -> String
write_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

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