Using the data storage type defined on this page for raster images, read an image from a PPM file (binary P6 prefered). (Read the definition of PPM file on Wikipedia.)

Task
Bitmap/Read a PPM file
You are encouraged to solve this task according to the task description, using any language you may know.

Task: Use write ppm file solution and grayscale image solution with this one in order to convert a color image to grayscale one.

Ada

<lang ada>with Ada.Characters.Latin_1; use Ada.Characters.Latin_1; with Ada.Integer_Text_IO; use Ada.Integer_Text_IO; with Ada.Streams.Stream_IO; use Ada.Streams.Stream_IO;

function Get_PPM (File : File_Type) return Image is

  use Ada.Characters.Latin_1;
  use Ada.Integer_Text_IO;
  function Get_Line return String is -- Skips comments
     Byte   : Character;
     Buffer : String (1..80);
  begin
     loop
        for I in Buffer'Range loop
           Character'Read (Stream (File), Byte);
           if Byte = LF then
              exit when Buffer (1) = '#';
              return Buffer (1..I - 1);
           end if;
           Buffer (I) := Byte;
        end loop;
        if Buffer (1) /= '#' then
           raise Data_Error;
        end if;
     end loop;
  end Get_Line;
  Height : Integer;
  Width  : Integer;

begin

  if Get_Line /= "P6" then
     raise Data_Error;
  end if;
  declare
     Line  : String  := Get_Line;
     Start : Integer := Line'First;
     Last  : Positive;
  begin
     Get (Line, Width, Last);                     Start := Start + Last;
     Get (Line (Start..Line'Last), Height, Last); Start := Start + Last;
     if Start <= Line'Last then
        raise Data_Error;
     end if;
     if Width < 1 or else Height < 1 then
        raise Data_Error;
     end if;
  end;
  if Get_Line /= "255" then
     raise Data_Error;
  end if;
  declare
     Result : Image (1..Height, 1..Width);
     Buffer : String (1..Width * 3);
     Index  : Positive;
  begin
     for I in Result'Range (1) loop
        String'Read (Stream (File), Buffer);
        Index := Buffer'First;
        for J in Result'Range (2) loop
           Result (I, J) :=
              (  R => Luminance (Character'Pos (Buffer (Index))),
                 G => Luminance (Character'Pos (Buffer (Index + 1))),
                 B => Luminance (Character'Pos (Buffer (Index + 2)))
              );
           Index := Index + 3;
        end loop;
     end loop;
     return Result;
  end;

end Get_PPM;</lang> The implementation propagates Data_Error when the file format is incorrect. End_Error is propagated when the file end is prematurely met. The following example illustrates conversion of a color file to grayscale. <lang ada>declare

  F1, F2 : File_Type;

begin

  Open (F1, In_File, "city.ppm");
  Create (F2, Out_File, "city_grayscale.ppm");
  Put_PPM (F2, Color (Grayscale (Get_PPM (F1))));
  Close (F1);
  Close (F2);

end;</lang>

AutoHotkey

<lang AutoHotkey>img := ppm_read("blue.ppm") x := img[4,4] ; get pixel(4,4) msgbox % "img: 4,4,R,G,B, RGB: " x.R ", " x.G ", " x.B ", " x.rgb() img.write("bluecopy.ppm") return

ppm_read(filename) {

 fileread, ppmo, % filename, utf-8
 loop, parse, ppmo, `n, `r
 {
   if (substr(A_LoopField, 1, 1) == "#")
     continue
   ppm_nocomment .= A_LoopField "`n"
 }
 index := 1  
 pos := 1
 while pos := regexmatch(ppm_nocomment, "\d+", pixel, pos)
 {
   pos := regexmatch(ppm_nocomment, "\s", x, pos)
   bitmap%A_Index% := pixel
   if (index == 4)
     Break
   index ++
   
 }
 type := bitmap1
 width := bitmap2
 height := bitmap3
 maxcolor := bitmap4
 bitmap := Bitmap(width, height, color(0,0,0))
 index := 1
 width := 1
 height := 1
 while pos := regexmatch(ppm_nocomment, "\d+", pixel, pos)
 {
   pix%A_Index% := pixel
   index++
   if (index > 3)

{

     index := 1
     pixel := Color(pix1, pix2, pix3)
     bitmap[height, width] := pixel
     if (width == bitmap.width)

{ width := 1 height += 1 }

     else

width++ }

  pos := regexmatch(ppm_nocomment, "\s", x, pos)
 }
return bitmap 

}

  1. include bitmap_storage.ahk ; from http://rosettacode.org/wiki/Basic_bitmap_storage/AutoHotkey

</lang>

C

It is up to the caller to open the file and pass the handler to the function. So this code can be used in Read image file through a pipe without modification. It only understands the P6 file format.

Interface:

<lang c>image get_ppm(FILE *pf);</lang>

Implementation:

<lang c>#include "imglib.h"

  1. define PPMREADBUFLEN 256

image get_ppm(FILE *pf) {

       char buf[PPMREADBUFLEN], *t;
       image img;
       unsigned int w, h, d;
       int r;
       
       if (pf == NULL) return NULL;
       t = fgets(buf, PPMREADBUFLEN, pf);
       if ( (t == NULL) || ( strncmp(buf, "P6\n", 3) != 0 ) ) return NULL;
       do
       { /* Px formats can have # comments after first line */
          t = fgets(buf, PPMREADBUFLEN, pf);
          if ( t == NULL ) return NULL;
       } while ( strncmp(buf, "#", 1) == 0 );
       r = sscanf(buf, "%u %u", &w, &h);
       if ( r < 2 ) return NULL;
       // The program fails if the first byte of the image is equal to 32. because
       // the fscanf eats the space and the image is read with some bit less
       r = fscanf(pf, "%u\n", &d);
       if ( (r < 1) || ( d != 255 ) ) return NULL;
       img = alloc_img(w, h);
       if ( img != NULL )
       {
           size_t rd = fread(img->buf, sizeof(pixel), w*h, pf);
           if ( rd < w*h )
           {
              free_img(img);
              return NULL;
           }
           return img;
       }

}</lang>

The following acts as a filter to convert a PPM file read from standard input into a PPM gray image, and it outputs the converted image to standard output (see Grayscale image, Write ppm file, and Raster graphics operations in general):

<lang c>#include <stdio.h>

  1. include "imglib.h"

int main() {

  image source;
  grayimage idest;
  
  source = get_ppm(stdin);
  idest = tograyscale(source);
  free_img(source);
  source = tocolor(idest);
  output_ppm(stdout, source);
  free_img(source); free_img((image)idest);
  return 0;

}</lang>

C#

Tested with this solution.

<lang csharp>using System.IO; class PPMReader {

   public static Bitmap ReadBitmapFromPPM(string file)
   {
       var reader = new BinaryReader(new FileStream(file, FileMode.Open));
       if (reader.ReadChar() != 'P' || reader.ReadChar() != '6')
           return null;
       reader.ReadChar(); //Eat newline
       string widths = "", heights = "";
       char temp;
       while ((temp = reader.ReadChar()) != ' ')
           widths += temp;
       while ((temp = reader.ReadChar()) >= '0' && temp <= '9')
           heights += temp;
       if (reader.ReadChar() != '2' || reader.ReadChar() != '5' || reader.ReadChar() != '5')
           return null;
       reader.ReadChar(); //Eat the last newline
       int width = int.Parse(widths),
           height = int.Parse(heights);
       Bitmap bitmap = new Bitmap(width, height);
       //Read in the pixels
       for (int y = 0; y < height; y++)
           for (int x = 0; x < width; x++)
               bitmap.SetPixel(x, y, new Bitmap.Color()
               {
                   Red = reader.ReadByte(),
                   Green = reader.ReadByte(),
                   Blue = reader.ReadByte()
               });
       return bitmap;
   }

}</lang>


D

This example uses storage defined on Basic bitmap storage problem page.

This is wrap-around defined storage, P6 binary mode.

Works with: tango

<lang D>import tango.core.Exception; import tango.io.FileConduit; import tango.io.MappedBuffer; import tango.io.stream.LineStream; import tango.io.protocol.Reader; import tango.text.convert.Integer;

class P6Image {

   class BadInputException : Exception { this() { super("Bad file format"); } }
   class NoImageException : Exception { this() { super("No image data"); } }
   static const char[] type = "P6";
   MappedBuffer fileBuf;
   ubyte _maxVal, gotImg;

public:

   RgbBitmap bitmap;
   this (FileConduit input) {
       fileBuf = new MappedBuffer(input);
       if (processHeader(new LineInput(fileBuf)))
           throw new BadInputException;
       if (processData(fileBuf))
           throw new BadInputException;
   }
   ubyte maxVal() { return _maxVal; }
   int processHeader(LineInput li) {
       char[] line;
       uint eaten;
       li.readln(line);
       if (line != type) return 1;
       li.readln(line);
       // skip comment lines
       while (line.length && line[0] == '#') li.readln(line);
       auto width = parse(line, 0, &eaten);
       auto height = parse(line[eaten..$], 0, &eaten);
       if (!eaten || width > 0xffff_ffff || height > 0xffff_ffff) return 1;
       li.readln(line);
       auto temp = parse(line, 0, &eaten);
       if (!eaten || temp > 255) return 1;
       _maxVal = temp;
       bitmap = RgbBitmap(width, height);
       gotImg = 1;
       return 0;
   }
   int processData(MappedBuffer mb) {
       if (! gotImg) throw new NoImageException;
       mb.fill(bitmap.data);
       return 0;
   }

}</lang>

Reading from file: <lang D>auto p6 = new P6Image(new FileConduit("image.ppm"));</lang>

E

<lang e>def chr := <import:java.lang.makeCharacter>.asChar

def readPPM(inputStream) {

 # Proper native-to-E stream IO facilities have not been designed and
 # implemented yet, so we are borrowing Java's. Poorly. This *will* be
 # improved eventually.
 
 # Reads one header token, skipping comments and whitespace, and exactly
 # one trailing whitespace character
 def readToken() {
   var token := ""
   var c := chr(inputStream.read())
   while (c == ' ' || c == '\t' || c == '\r' || c == '\n' || c == '#') {
     if (c == '#') {
       while (c != '\n') { c := chr(inputStream.read()) }
     }
     # skip over initial whitespace
     c := chr(inputStream.read())
   }
   while (!(c == ' ' || c == '\t' || c == '\r' || c == '\n')) {
     if (c == '#') {
       while (c != '\n') { c := chr(inputStream.read()) }
     } else {
       token += E.toString(c)
       c := chr(inputStream.read())
     }
   }
   return token
 }
 # Header
 require(readToken() == "P6")
 def width := __makeInt(readToken())
 def height := __makeInt(readToken())
 def maxval := __makeInt(readToken())
 def size := width * height * 3
 # Body
 # See Basic bitmap storage for the definition and origin of sign()
 def data := <elib:tables.makeFlexList>.fromType(<type:java.lang.Byte>, size)
 if (maxval >= 256) {
   for _ in 1..size {
     data.push(sign((inputStream.read() * 256 + inputStream.read()) * 255 // maxval))
   }
 } else {
   for _ in 1..size {
     data.push(sign(inputStream.read() * 255 // maxval))
   }
 }
 def image := makeImage(width, height)
 image.replace(data.snapshot())
 return image

}</lang>Note: As of this writing the grayscale image task has not been implemented, so the task code (below) won't actually run yet. But readPPM above has been tested separately.

<lang e>def readPPMTask(inputFile, outputFile) {

 makeGrayscale \
   .fromColor(readPPM(<import:java.io.makeFileInputStream>(inputFile))) \
   .toColor() \
   .writePPM(<import:java.io.makeFileOutputStream>(outputFile))

}</lang>

Forth

<lang forth>: read-ppm { fid -- bmp }

 pad dup 80 fid read-line throw 0= abort" Partial line"
 s" P6" compare abort" Only P6 supported."
 pad dup 80 fid read-line throw 0= abort" Partial line"
 0. 2swap >number
 1 /string		\ skip space
 0. 2swap >number
 2drop drop nip    ( w h )
 bitmap { bmp }
 pad dup 80 fid read-line throw 0= abort" Partial line"
 s" 255" compare abort" Only 8-bits per color channel supported"
 0 pad !
 bmp bdim
 0 do
   dup 0 do
     pad 3 fid read-file throw
     3 - abort" Not enough pixel data in file"
     pad @ i j bmp b!
   loop
 loop drop
 bmp ;

\ testing round-trip 4 3 bitmap value test red test bfill green 1 2 test b!

s" red.ppm" w/o create-file throw test over write-ppm close-file throw

s" red.ppm" r/o open-file throw dup read-ppm value test2 close-file throw

bsize ( bmp -- len ) bdim * pixels bdata ;

test dup bsize test2 dup bsize compare . \ 0 if identical</lang>

Fortran

Works with: Fortran version 90 and later

(This function is part of module RCImageIO, see Write ppm file)

<lang fortran>subroutine read_ppm(u, img)

 integer, intent(in) :: u
 type(rgbimage), intent(out) :: img
 integer :: i, j, ncol, cc
 character(2) :: sign
 character :: ccode
 
 img%width = 0
 img%height = 0
 nullify(img%red)
 nullify(img%green)
 nullify(img%blue)
 read(u, '(A2)') sign
 read(u, *) img%width, img%height
 read(u, *) ncol
 write(0,*) sign
 write(0,*) img%width, img%height
 write(0,*) ncol
 if ( ncol /= 255 ) return
 call alloc_img(img, img%width, img%height)
 if ( valid_image(img) ) then
    do j=1, img%height
       do i=1, img%width
          read(u, '(A1)', advance='no', iostat=status) ccode
          cc = iachar(ccode)
          img%red(i,j) = cc
          read(u, '(A1)', advance='no', iostat=status) ccode
          cc = iachar(ccode)
          img%green(i,j) = cc
          read(u, '(A1)', advance='no', iostat=status) ccode
          cc = iachar(ccode)
          img%blue(i,j) = cc
       end do
    end do
 end if

end subroutine read_ppm</lang>

Notes:

  • doing formatted I/O with Fortran is a pain... And unformatted does not mean free; Fortran2003 has streams, but they are not implemented (yet) in GNU Fortran compiler. Here (as in the write part) I've tried to handle the PPM format through formatted I/O. The tests worked but I have not tried still everything.
  • comments after the first line are not handled

Haskell

The definition of Bitmap.Netpbm.readNetpbm is given here. <lang haskell>import Bitmap import Bitmap.RGB import Bitmap.Gray import Bitmap.Netpbm

import Control.Monad import Control.Monad.ST

main =

   (readNetpbm "original.ppm" :: IO (Image RealWorld RGB)) >>=
   stToIO . toGrayImage >>=
   writeNetpbm "new.pgm"</lang>

The above writes a PGM, not a PPM, since the image being output is in grayscale. If you actually want a gray PPM, convert the Image RealWorld Gray back to an Image RealWorld RGB first: <lang haskell>main =

   (readNetpbm "original.ppm" :: IO (Image RealWorld RGB)) >>=
   stToIO . (toRGBImage <=< toGrayImage) >>=
   writeNetpbm "new.ppm"</lang>

J

Solution:
Uses makeRGB from Basic bitmap storage. <lang j>require 'files'

readppm=: monad define

 dat=. fread y                                           NB. read from file
 msk=. 1 ,~ (*. 3 >: +/\) (LF&=@}: *. '#'&~:@}.) dat     NB. mark field ends
 't wbyh maxval dat'=. msk <;._2 dat                     NB. parse
 'wbyh maxval'=. 2 1([ {. [: _99&". (LF,' ')&charsub)&.> wbyh;maxval  NB. convert to numeric
 if. (_99 0 +./@e. wbyh,maxval) +. 'P6' -.@-: 2{.t do. _1 return. end.
 (a. i. dat) makeRGB |.wbyh                              NB. convert to basic bitmap format

)</lang>

Example:
Using utilities and file from Grayscale image and Write ppm file.
Writes a gray PPM file (a color format) which is bigger than necessary. A PGM file would be more appropriate. <lang j>myimg=: readppm jpath '~temp/myimg.ppm' myimgGray=: toColor toGray myimg myimgGray writeppm jpath '~temp/myimgGray.ppm'</lang>

OCaml

<lang ocaml>let read_ppm ~filename =

 let ic = open_in filename in
 let line = input_line ic in
 if line <> "P6" then invalid_arg "not a P6 ppm file";
 let line = input_line ic in
 let line =
   try if line.[0] = '#'  (* skip comments *)
   then input_line ic
   else line
   with _ -> line
 in
 let width, height =
   Scanf.sscanf line "%d %d" (fun w h -> (w, h))
 in
 let line = input_line ic in
 if line <> "255" then invalid_arg "not a 8 bit depth image";
 let all_channels =
   let kind = Bigarray.int8_unsigned
   and layout = Bigarray.c_layout
   in
   Bigarray.Array3.create kind layout 3 width height
 in
 let r_channel = Bigarray.Array3.slice_left_2 all_channels 0
 and g_channel = Bigarray.Array3.slice_left_2 all_channels 1
 and b_channel = Bigarray.Array3.slice_left_2 all_channels 2
 in
 for y = 0 to pred height do
   for x = 0 to pred width do
     r_channel.{x,y} <- (input_byte ic);
     g_channel.{x,y} <- (input_byte ic);
     b_channel.{x,y} <- (input_byte ic);
   done;
 done;
 close_in ic;
 (all_channels,
  r_channel,
  g_channel,
  b_channel)</lang>

and converting a given color file to grayscale: <lang ocaml>let () =

 let img = read_ppm ~filename:"logo.ppm" in
 let img = to_color(to_grayscale ~img) in
 output_ppm ~oc:stdout ~img;
</lang>

sending the result to stdout allows to see the result without creating a temporary file sending it through a pipe to the display utility of ImageMagick:

ocaml script.ml | display -

Oz

The read function in module "BitmapIO.oz": <lang oz>functor import

  Bitmap
  Open

export

  Read
  %% Write

define

  fun {Read Filename}
     F = {New Open.file init(name:Filename)}
     fun {ReadColor8 _}

Bytes = {F read(list:$ size:3)}

     in

{List.toTuple color Bytes}

     end
     fun {ReadColor16 _}

Bytes = {F read(list:$ size:6)}

     in

{List.toTuple color {Map {PairUp Bytes} FromBytes}}

     end
  in
     try

Magic = {F read(size:2 list:$)} if Magic \= "P6" then raise bitmapIO(read unsupportedFormat(Magic)) end end Width = {ReadNumber F} Height = {ReadNumber F} MaxVal = {ReadNumber F} MaxVal =< 0xffff = true Reader = if MaxVal =< 0xff then ReadColor8 else ReadColor16 end B = {Bitmap.new Width Height}

     in

{Bitmap.transform B Reader} B

     finally

{F close}

     end
  end
  fun {ReadNumber F}
     Ds
  in
     {SkipWS F}
     Ds = for collect:Collect break:Break do

[C] = {F read(list:$ size:1)} in if {Char.isDigit C} then {Collect C} else {Break} end end

     {SkipWS F}
     {String.toInt Ds}
  end
  proc {SkipWS F}
     [C] = {F read(list:$ size:1)}
  in
     if {Char.isSpace C} then {SkipWS F}
     elseif C == &# then

{SkipLine F}

     else

{F seek(whence:current offset:~1)}

     end
  end
  proc {SkipLine F}
     [C] = {F read(list:$ size:1)}
  in
     if C \= &\n andthen  C \= &\r then {SkipLine F} end
  end
  
  fun {PairUp Xs}
     case Xs of X1|X2|Xr then [X1 X2]|{PairUp Xr}
     [] nil then nil
     end
  end
  fun {FromBytes [C1 C2]}
     C1 * 0x100 + C2
  end
  %% Omitted: Write

end</lang>

The actual task: <lang oz>declare

 [BitmapIO Grayscale] = {Module.link ['BitmapIO.ozf' 'Grayscale.ozf']}
 B = {BitmapIO.read "image.ppm"}
 G = {Grayscale.toGraymap B}

in

 {BitmapIO.write {Grayscale.fromGraymap G} "greyimage.ppm"}</lang>

Perl

Library: Imlib2

<lang perl>#! /usr/bin/perl

use strict; use Image::Imlib2;

my $img = Image::Imlib2->load("out0.ppm");

  1. let's do something with it now

$img->set_color(255, 255, 255, 255); $img->draw_line(0,0, $img->width,$img->height); $img->image_set_format("png"); $img->save("out1.png");

exit 0;</lang>

PL/I

<lang PL/I> /* BITMAP FILE: read in a file in PPM format, P6 (binary). 14/5/2010 */ test: procedure options (main);

  declare (m, n, max_color, i, j) fixed binary (31);
  declare ch character (1), ID character (2);
  declare 1 pixel union,
           2 color bit(24) aligned,
              3 R char (1),
              3 G char (1),
              3 B char (1);
  declare in file record;
  open file (in) title ('/IMAGE.PPM,TYPE(FIXED),RECSIZE(1)' ) input;
  call get_char(ch);
  ID = ch;
  call get_char (ch);
  substr(ID, 2,1) = ch;
  /* Read in the dimensions of the image */
  call get_integer (m);
  call get_integer (n);
  /* Read in the maximum color size used */
  call get_integer (max_color);
     /* The previous call reads in ONE line feed or CR or other terminator */
     /* character. */

begin;

  declare image (0:m-1,0:n-1) bit (24);
  do i = 0 to hbound(image, 1);
     do j = 0 to hbound(image,2);
        read file (in) into (R);
        read file (in) into (G);
        read file (in) into (B);
        image(i,j) = color;
     end;
  end;

end;

get_char: procedure (ch);

  do until (ch ^= ' ');
     read file (in) into (ch) (a(1))
  end;

end get_char;

get_integer: procedure (value);

  declare value fixed binary;
  do until (ch = ' ');
     read file (in) into (ch);
  end;
  value = 0;
  do until (is_digit(ch));
     value = value*10 + ch;
     read file (ch) into (ch);
  end;

end get_integer;

end test; </lang>

PureBasic

<lang PureBasic>Structure PPMColor

 r.c
 g.c
 b.c

EndStructure

Procedure LoadImagePPM(Image, file$)

 ; Author Roger Rösch (Nickname Macros)
 IDFile = ReadFile(#PB_Any, file$)
 If IDFile
   If CreateImage(Image, 1, 1)
     Format$ = ReadString(IDFile)
     ReadString(IDFile) ; skip comment
     Dimensions$ = ReadString(IDFile)
     w           = Val(StringField(Dimensions$, 1, " "))
     h           = Val(StringField(Dimensions$, 2, " "))
     ResizeImage(Image, w, h)
     StartDrawing(ImageOutput(Image))
     max = Val(ReadString(IDFile))           ; Maximal Value for a color
     Select Format$
       Case "P3" ; File in ASCII format
         ; Exract everey number remaining in th file into an array using an RegEx
         Stringlen = Lof(IDFile) - Loc(IDFile)
         content$  = Space(Stringlen)
         Dim color.s(0)
         ReadData(IDFile, @content$, Stringlen)
         CreateRegularExpression(1, "\d+")
         ExtractRegularExpression(1, content$, color())
         ; Plot color information on our empty Image
         For y = 0 To h - 1
           For x = 0 To w - 1
             pos = (y*w + x)*3
             r=Val(color(pos))*255 / max
             g=Val(color(pos+1))*255 / max
             b=Val(color(pos+2))*255 / max
             Plot(x, y, RGB(r,g,b))
           Next
         Next
       Case "P6" ;File In binary format
         ; Read whole bytes into a buffer because its faster than reading single ones
         Bufferlen = Lof(IDFile) - Loc(IDFile)
         *Buffer   = AllocateMemory(Bufferlen)
         ReadData(IDFile, *Buffer, Bufferlen)
         ; Plot color information on our empty Image
         For y = 0 To h - 1
           For x = 0 To w - 1
             *color.PPMColor = pos + *Buffer
             Plot(x, y, RGB(*color\r*255 / max, *color\g*255 / max, *color\b*255 / max))
             pos + 3
           Next
         Next
     EndSelect
     StopDrawing()
     ; Return 1 if successfully loaded to behave as other Purebasic functions
     ProcedureReturn 1 
   EndIf
 EndIf

EndProcedure</lang>

Python

Works with: Python version 3.1

Extending the example given here <lang python># With help from http://netpbm.sourceforge.net/doc/ppm.html

  1. String masquerading as ppm file (version P3)

import io

ppmtxt = P3

  1. feep.ppm

4 4 15

0  0  0    0  0  0    0  0  0   15  0 15
0  0  0    0 15  7    0  0  0    0  0  0
0  0  0    0  0  0    0 15  7    0  0  0

15 0 15 0 0 0 0 0 0 0 0 0


def tokenize(f):

   for line in f:
       if line[0] != '#':
           for t in line.split():
               yield t

def ppmp3tobitmap(f):

   t = tokenize(f)
   nexttoken = lambda : next(t)
   assert 'P3' == nexttoken(), 'Wrong filetype'
   width, height, maxval = (int(nexttoken()) for i in range(3))
   bitmap = Bitmap(width, height, Colour(0, 0, 0))
   for h in range(height-1, -1, -1):
       for w in range(0, width):
           bitmap.set(w, h, Colour( *(int(nexttoken()) for i in range(3))))
   return bitmap
   

print('Original Colour PPM file') print(ppmtxt) ppmfile = io.StringIO(ppmtxt) bitmap = ppmp3tobitmap(ppmfile) print('Grey PPM:') bitmap.togreyscale() ppmfileout = io.StringIO() bitmap.writeppmp3(ppmfileout) print(ppmfileout.getvalue())


The print statements above produce the following output:

Original Colour PPM file P3

  1. feep.ppm

4 4 15

0  0  0    0  0  0    0  0  0   15  0 15
0  0  0    0 15  7    0  0  0    0  0  0
0  0  0    0  0  0    0 15  7    0  0  0

15 0 15 0 0 0 0 0 0 0 0 0

Grey PPM: P3

  1. generated from Bitmap.writeppmp3

4 4 11

   0  0  0    0  0  0    0  0  0    4  4  4
   0  0  0   11 11 11    0  0  0    0  0  0
   0  0  0    0  0  0   11 11 11    0  0  0
   4  4  4    0  0  0    0  0  0    0  0  0

</lang>

Ruby

Extending Basic_bitmap_storage#Ruby <lang ruby>class Pixmap

 # 'open' is a class method
 def self.open(filename)
   bitmap = nil
   File.open(filename, 'r') do |f|
     header = [f.gets.chomp, f.gets.chomp, f.gets.chomp]
     width, height = header[1].split.map {|n| n.to_i }
     if header[0] != 'P6' or header[2] != '255' or width < 1 or height < 1
       raise StandardError, "file '#{filename}' does not start with the expected header"
     end
     f.binmode
     bitmap = self.new(width, height)
     height.times do |y|
       width.times do |x|
         # read 3 bytes
         red, green, blue = f.read(3).unpack('C3')
         bitmap[x,y] = RGBColour.new(red, green, blue)
       end
     end
   end
   bitmap
 end

end

  1. create an image: a green cross on a blue background

colour_bitmap = Pixmap.new(20, 30) colour_bitmap.fill(RGBColour::BLUE) colour_bitmap.height.times {|y| [9,10,11].each {|x| colour_bitmap[x,y]=RGBColour::GREEN}} colour_bitmap.width.times {|x| [14,15,16].each {|y| colour_bitmap[x,y]=RGBColour::GREEN}} colour_bitmap.save('testcross.ppm')

  1. then, convert to grayscale

Pixmap.open('testcross.ppm').to_grayscale!.save('testgray.ppm')</lang>

Tcl

Library: Tk

The actual PPM reader is built into the photo image engine: <lang tcl>package require Tk

proc readPPM {image file} {

   $image read $file -format ppm

}</lang> Thus, to read a PPM, convert it to grayscale, and write it back out again becomes this (which requires Tcl 8.6 for try/finally); the PPM reader and writer are inlined because they are trivial at the script level: <lang tcl>package require Tk

proc grayscaleFile {filename {newFilename ""}} {

   set buffer [image create photo]
   if {$newFilename eq ""} {set newFilename $filename}
   try {
       $buffer read $filename -format ppm
       set w [image width $buffer]
       set h [image height $buffer]
       for {set x 0} {$x<$w} {incr x} {
           for {set y 0} {$y<$h} {incr y} {
               lassign [$buffer get $x $y] r g b
               set l [expr {int(0.2126*$r + 0.7152*$g + 0.0722*$b)}]
               $buffer put [format "#%02x%02x%02x" $l $l $l] -to $x $y
           }
       }
       $buffer write $newFilename -format ppm
   } finally {
       image delete $buffer
   }

}</lang>

However, the Tk library also has built-in the ability to convert code to grayscale directly during the saving of an image to a file, leading to this minimal solution: <lang tcl>package require Tk

proc grayscaleFile {filename {newFilename ""}} {

   set buffer [image create photo]
   if {$newFilename eq ""} {set newFilename $filename}
   try {
       $buffer read $filename -format ppm
       $buffer write $newFilename -format ppm -grayscale
   } finally {
       image delete $buffer
   }

}</lang>

Vedit macro language

<lang vedit>// Load a PPM file // @10 = filename // On return: // #10 points to buffer containing pixel data, // #11 = width, #12 = height.

LOAD_PPM:

File_Open(@10) BOF Search("|X", ADVANCE) // skip "P6"

  1. 11 = Num_Eval(ADVANCE) // #11 = width

Match("|X", ADVANCE) // skip separator

  1. 12 = Num_Eval(ADVANCE) // #12 = height

Match("|X", ADVANCE) Search("|X", ADVANCE) // skip maxval (assume 255) Del_Block(0,CP) // remove the header Return</lang>

Example of usage. In addition to LOAD_PPM routine above, you need routine RGB_TO_GRAYSCALE from Grayscale image and routine SAVE_PPM from Write ppm file. <lang vedit>// Load RGB image Reg_Set(10, "|(USER_MACRO)\example.ppm") Call("LOAD_PPM")

// Convert to grayscale

  1. 10 = Buf_Num

Call("RGB_TO_GRAYSCALE") Buf_Switch(#10) Buf_Quit(OK)

// Convert to RGB Call("GRAYSCALE_TO_RGB")

// Save the image Reg_Set(10, "|(USER_MACRO)\example_gray.ppm") Call("SAVE_PPM")

// Cleanup and exit Buf_Switch(#20) Buf_Quit(OK) return</lang>