Grayscale image: Difference between revisions

From Rosetta Code
Content added Content deleted
(→‎{{header|Perl}}: ++ Octave)
Line 454: Line 454:
b_channel)
b_channel)
</lang>
</lang>

=={{header|Octave}}==

'''Use package''': image

<lang octave>function [grayImage] = colortograyscale(inputImage)
grayImage = rgb2gray(inputImage);</lang>

Differently from [[Grayscale image#MATLAB|MATLAB]], the grayscale is computed as mean of the three RGB values. Changing this non-optimal behaviour is a matter of fixing three lines in the <tt>rgb2gray.m</tt> file; since it's a GPL-ed code, here it is a semplified version (error checking, usage help, argument checking removed)

<lang octave>function gray = rgb2gray (rgb)
switch(class(rgb))
case "double"
gray = luminance(rgb);
case "uint8"
gray = uint8(luminance(rgb));
case "uint16"
gray = uint16(luminance(rgb));
endswitch
endfunction

function lum = luminance(rgb)
lum = 0.2126*rgb(:,:,1) + 0.7152*rgb(:,:,2) + 0.0722*rgb(:,:,3);
endfunction</lang>

Original code of the <tt>rgb2gray.m</tt> in the image package version 1.0.8 is by Kai Habel (under the GNU General Public License)


=={{header|Perl}}==
=={{header|Perl}}==

Revision as of 12:29, 3 October 2009

Task
Grayscale image
You are encouraged to solve this task according to the task description, using any language you may know.

Many image processing algorithms are defined for grayscale (or else monochromatic) images. Extend the data storage type defined on this page to support grayscale images. Define two operations, one to convert a color image to a grayscale image and one for the backward conversion. To get luminance of a color use the formula recommended by CIE:

L = 0.2126·R + 0.7152·G + 0.0722·B

When using floating-point arithmetic make sure that rounding errors would not cause run-time problems or else distorted results when calculated luminance is stored as an unsigned integer.

Ada

<lang ada> type Grayscale_Image is array (Positive range <>, Positive range <>) of Luminance; </lang> Conversion to a grayscale image: <lang ada> function Grayscale (Picture : Image) return Grayscale_Image is

  type Extended_Luminance is range 0..10_000_000;
  Result : Grayscale_Image (Picture'Range (1), Picture'Range (2));
  Color  : Pixel;

begin

  for I in Picture'Range (1) loop
     for J in Picture'Range (2) loop
        Color := Picture (I, J);
        Result (I, J) :=
           Luminance
           (  (  2_126 * Extended_Luminance (Color.R)
              +  7_152 * Extended_Luminance (Color.G)
              +    722 * Extended_Luminance (Color.B)
              )
           /  10_000
           );
     end loop;
  end loop;
  return Result;

end Grayscale; </lang> Conversion to a color image: <lang ada> function Color (Picture : Grayscale_Image) return Image is

  Result : Image (Picture'Range (1), Picture'Range (2));

begin

  for I in Picture'Range (1) loop
     for J in Picture'Range (2) loop
        Result (I, J) := (others => Picture (I, J));
     end loop;
  end loop;
  return Result;

end Color; </lang>

C

Definition/interface for a grayscale image.

<lang c>typedef unsigned char luminance; typedef luminance pixel1[1]; typedef struct {

  unsigned int width;
  unsigned int height;
  luminance *buf;

} grayimage_t; typedef grayimage_t *grayimage;

grayimage alloc_grayimg(unsigned int, unsigned int); grayimage tograyscale(image); image tocolor(grayimage);</lang>

The same as alloc_img, but for grayscale images.

<lang c> grayimage alloc_grayimg(unsigned int width, unsigned int height) {

    grayimage img;
    img = malloc(sizeof(grayimage_t));
    img->buf = malloc(width*height*sizeof(pixel1));
    img->width = width;
    img->height = height;
    return img;

} </lang>

Convert from color image to grayscale image.

<lang c> grayimage tograyscale(image img) {

  unsigned int x, y;
  grayimage timg;
  double rc, gc, bc, l;
  unsigned int ofs;
  timg = alloc_grayimg(img->width, img->height);
  
  for(x=0; x < img->width; x++)
  {
     for(y=0; y < img->height; y++)
     {
       ofs = (y * img->width) + x;
       rc = (double) img->buf[ofs][0];
       gc = (double) img->buf[ofs][1];
       bc = (double) img->buf[ofs][2];
       l = 0.2126*rc + 0.7152*gc + 0.0722*bc;
       timg->buf[ofs][0] = (luminance) (l+0.5);
     }
  }
  return timg;

} </lang>

And back from a grayscale image to a color image.

<lang c> image tocolor(grayimage img) {

  unsigned int x, y;
  image timg;
  luminance l;
  unsigned int ofs;
  timg = alloc_img(img->width, img->height);
  
  for(x=0; x < img->width; x++)
  {
     for(y=0; y < img->height; y++)
     {
       ofs = (y * img->width) + x;
       l = img->buf[ofs][0];
       timg->buf[ofs][0] = l;
       timg->buf[ofs][1] = l;
       timg->buf[ofs][2] = l;
     }
  }
  return timg;

} </lang>

Notes

  • tocolor and tograyscale do not free the previous image, so it must be freed normally calling free_img. With a cast we can use the same function also for grayscale images, or we can define something like

<lang c>

  1. define free_grayimg(IMG) free_img((image)(IMG))

</lang>

  • Luminance is rounded. Since the C implementation is based on unsigned char (256 possible values per components), L can be at most 255.0 and rounding gives 255, as we expect. Changing the color_component type would only change 256, 255.0 and 255 values here written in something else, the code would work the same.

D

This example uses Bitmap template as defined on Basic bitmap storage problem page.


<lang D> struct Lumin {

   ubyte[1] value;
   void opCall(ubyte l) { value[0] = l; }
   void opCall(ubyte[1] v) { value[] = v[]; }
   
   ubyte l() { return value[0]; }

}

alias Bitmap!(Lumin) GrayBitmap;

GrayBitmap rgbToGray(RgbBitmap bitmap) {

   auto gb = GrayBitmap(bitmap.width, bitmap.height);
   int x, y;
   foreach (ref elem; gb) {
       elem(bitmap[x, y].lumAVG);
       if (++x == bitmap.width) { x = 0; y++; }
   }
   return gb;

}

RgbBitmap grayToRgb(GrayBitmap gray) {

   auto rgb = RgbBitmap(gray.width, gray.height);
   int x, y;
   foreach (ref elem; rgb) {
       elem(gray[x, y].l);
       if (++x == gray.width) { x = 0; y++; }
   }
   return rgb;

} </lang>


Adding the following opCall methods to Lumin and Rgb structs would allow to create simple conversion function template instead of two separate functions. <lang D> //in Rgb struct:

   void opCall(Rgb v) { value[] = v.value[]; }

//in Lumin struct:

   void opCall(Lumin l) { value[] = l.value[]; }

</lang>

Conversion function template: <lang D> Bitmap!(TO) convert(FR, TO)(Bitmap!(FR) source, TO delegate(FR) dg) {

   auto dest = Bitmap!(TO)(source.width, source.height);
   int x, y;
   foreach (ref elem; dest) {
       elem( dg(source[x, y]) );
       if (++x == source.width) { x = 0; y++; }
   }
   return dest;

} </lang>

Sample usage of conversion function: <lang D> // assuming t0 is of RgbBitmap type.. // convert RgbBitmap to GrayBitmap auto t1 = convert(t0, delegate Lumin(Rgb v) { Lumin res; res(cast(ubyte)(0.2126*v.r + 0.7152*v.g + 0.0722*v.b)); return res; } ); // convert Graybitmap to grayscale - RgbBitmap auto t2 = convert(t1, delegate Rgb(Lumin v) { Rgb res; res(v.l); return res; }); </lang>

Forth

\ grayscale bitmap (without word-alignment for scan lines)

\ bdim, bwidth, bdata all work with graymaps

: graymap ( w h -- gmp )
  2dup * bdata allocate throw
  dup >r 2! r> ;

: gxy ( x y gmp -- addr )
  dup bwidth rot * rot + swap bdata + ;

: g@ ( x y gmp -- c ) gxy c@ ;
: g! ( c x y bmp -- ) gxy c! ;

: gfill ( c gmp -- )
  dup bdata swap bdim * rot fill ;

: gshow ( gmp -- )
  dup bdim
  0 do cr
    dup 0 do
      over i j rot g@ if [char] * emit else space then
    loop
  loop
  2drop ;
\ RGB <-> Grayscale
: lum>rgb ( 0..255 -- pixel )
   dup 8 lshift or
   dup 8 lshift or ;

: pixel>rgb ( pixel -- r g b )
  256 /mod 256 /mod ;
: rgb>lum ( pixel -- 0..255 )
  pixel>rgb
   722 *   swap
  7152 * + swap
  2126 * + 10000 / ;

: bitmap>graymap ( bmp -- gmp )
  dup bdim graymap
  dup bdim nip 0 do
    dup bwidth 0 do
      over i j rot b@ rgb>lum
      over i j rot g!
    loop
  loop nip ;

: graymap>bitmap ( gmp -- bmp )
  dup bdim bitmap
  dup bdim nip 0 do
    dup bwidth 0 do
      over i j rot g@ lum>rgb
      over i j rot b!
    loop
  loop nip ;

Fortran

(These fragments should be added to RCImageBasic module, see Basic bitmap storage)

First let's define a new type; the sc stands for Single Channel, which can be luminance (as it is here).

<lang fortran> type scimage

    integer, dimension(:,:), pointer :: channel
    integer :: width, height
 end type scimage</lang>

In order to allow proper overloading, the following subroutines of the storage should be renamed appending the _rgb suffix: valid_image, inside_image, alloc_img, free_img, fill_img, get_pixel, put_pixel, init_img. The single channel version would be named with the _sc suffix, then we should define the proper interfaces to use the already written code as before. Here there are only the interfaces and subroutines needed for the task.

<lang fortran> interface alloc_img

    module procedure alloc_img_rgb, alloc_img_sc
 end interface
 interface free_img
    module procedure free_img_rgb, free_img_sc
 end interface</lang>

Now we can define useful interfaces and subroutines more task-related:

<lang fortran> interface assignment(=)

    module procedure rgbtosc, sctorgb
 end interface</lang>

<lang fortran> subroutine alloc_img_sc(img, w, h)

   type(scimage) :: img
   integer, intent(in) :: w, h
   allocate(img%channel(w, h))
   img%width = w
   img%height = h
 end subroutine alloc_img_sc
 subroutine free_img_sc(img)
   type(scimage) :: img
   if ( associated(img%channel) ) deallocate(img%channel)
 end subroutine free_img_sc
 subroutine rgbtosc(sc, colored)
   type(rgbimage), intent(in) :: colored
   type(scimage), intent(inout) :: sc
   if ( ( .not. valid_image(sc) ) .and. valid_image(colored) ) then
      call alloc_img(sc, colored%width, colored%height)
   end if
   if ( valid_image(sc) .and. valid_image(colored) ) then
      sc%channel = floor(0.2126*colored%red + 0.7152*colored%green + &
                         0.0722*colored%blue)
   end if
   
 end subroutine rgbtosc
 subroutine sctorgb(colored, sc)
   type(scimage), intent(in) :: sc
   type(rgbimage), intent(inout) :: colored
   if ( ( .not. valid_image(colored) ) .and. valid_image(sc) ) then
      call alloc_img_rgb(colored, sc%width, sc%height)
   end if
   if ( valid_image(sc) .and. valid_image(colored) ) then
      colored%red = sc%channel
      colored%green = sc%channel
      colored%blue = sc%channel
   end if
 end subroutine sctorgb</lang>

Usage example (fragment) which can be used to convert from rgb image to grayscale image and back (since we only can output the rgb kind):

<lang fortran>type(scimage) :: gray type(rgbimage) :: animage

 ! ... here we "load" or create animage
 ! while gray must be created or initialized to null
 ! or errors can arise...
 call init_img(gray)
 gray = animage
 animage = gray
 call output_ppm(an_unit, animage)</lang>

Haskell

<lang haskell>module Bitmap.Gray(module Bitmap.Gray) where

import Bitmap import Control.Monad.ST

newtype Gray = Gray Int deriving (Eq, Ord)

instance Color Gray where

   luminance (Gray x) = x
   black = Gray 0
   white = Gray 255
   toNetpbm = map $ toEnum . luminance
   fromNetpbm = map $ Gray . fromEnum
   netpbmMagicNumber _ = "P5"
   netpbmMaxval _ = "255"

toGrayImage :: Color c => Image s c -> ST s (Image s Gray) toGrayImage = mapImage $ Gray . luminance</lang>

A Gray image can be converted to an RGB image with Bitmap.RGB.toRGBImage, defined here.

J

Color bitmap structure and basic functions for manipulations with it are described here.

Grayscale image is stored as two-dimensional array of luminance values. Allowed luminance scale is the same as for the color bitmap; the functions below are neutral to scale.

<lang j> NB. converts the image to grayscale according to formula NB. L = 0.2126*R + 0.7152*G + 0.0722*B toGray=: <. @: (+/) @: (0.2126 0.7152 0.0722 & *)"1

NB. converts grayscale image to the color image, with all channels equal toColor=: 3 & $"0 0

</lang>

Example:

<lang j> viewImage toColor toGray myimg </lang>

MATLAB

Built in colour to grayscale converter uses the following forumula: 0.2989*R + 0.5870*G + 0.1140*B <lang Matlab>function [grayImage] = colortograyscale(inputImage)

  grayImage = rgb2gray(inputImage);</lang>

OCaml

Conversion to a grayscale image: <lang ocaml> let to_grayscale ~img:(_, r_channel, g_channel, b_channel) =

 let width = Bigarray.Array2.dim1 r_channel
 and height = Bigarray.Array2.dim2 r_channel in
 let gray_channel =
   let kind = Bigarray.int8_unsigned
   and layout = Bigarray.c_layout
   in
   (Bigarray.Array2.create kind layout width height)
 in
 for y = 0 to pred height do
   for x = 0 to pred width do
     let r = r_channel.{x,y}
     and g = g_channel.{x,y}
     and b = b_channel.{x,y} in
     let v = (2_126 * r +  7_152 * g + 722 * b) / 10_000 in
     gray_channel.{x,y} <- v;
   done;
 done;
 (gray_channel)

</lang>

Conversion to a color image: <lang ocaml> let to_color ~img:gray_channel =

 let width = Bigarray.Array2.dim1 gray_channel
 and height = Bigarray.Array2.dim2 gray_channel in
 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
 Bigarray.Array2.blit gray_channel r_channel;
 Bigarray.Array2.blit gray_channel g_channel;
 Bigarray.Array2.blit gray_channel b_channel;
 (all_channels,
  r_channel,
  g_channel,
  b_channel)

</lang>

Octave

Use package: image

<lang octave>function [grayImage] = colortograyscale(inputImage)

  grayImage = rgb2gray(inputImage);</lang>

Differently from MATLAB, the grayscale is computed as mean of the three RGB values. Changing this non-optimal behaviour is a matter of fixing three lines in the rgb2gray.m file; since it's a GPL-ed code, here it is a semplified version (error checking, usage help, argument checking removed)

<lang octave>function gray = rgb2gray (rgb)

   switch(class(rgb))
   case "double"
     gray = luminance(rgb);
   case "uint8"
     gray = uint8(luminance(rgb));
   case "uint16"
     gray = uint16(luminance(rgb));
   endswitch

endfunction

function lum = luminance(rgb)

  lum = 0.2126*rgb(:,:,1) + 0.7152*rgb(:,:,2) + 0.0722*rgb(:,:,3); 

endfunction</lang>

Original code of the rgb2gray.m in the image package version 1.0.8 is by Kai Habel (under the GNU General Public License)

Perl

Library: Imlib2

Since we are using Imlib2, this one does not implement really a gray-scale (single channel) storage; it only converts an RGB image to an RGB image with the same three colour components for each pixel (which result in a gray-scale-like image)

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

use strict; use Image::Imlib2;

sub tograyscale {

   my $img = shift;
   my $gimg = Image::Imlib2->new($img->width, $img->height);
   for ( my $x = 0; $x < $gimg->width; $x++ ) {

for ( my $y = 0; $y < $gimg->height; $y++ ) { my ( $r, $g, $b, $a ) = $img->query_pixel($x, $y); my $gray = int(0.2126 * $r + 0.7152 * $g + 0.0722 * $b); # discard alpha info... $gimg->set_color($gray, $gray, $gray, 255); $gimg->draw_point($x, $y); }

   }
   return $gimg;

}

my $animage = Image::Imlib2->load("Lenna100.jpg"); my $gscale = tograyscale($animage); $gscale->set_quality(80); $gscale->save("Lennagray.jpg");

exit 0;</lang>

Python

Works with: Python version 3.1

Extending the example given here <lang python># String masquerading as ppm file (version P3) import io ppmfileout = io.StringIO()

def togreyscale(self):

   for h in range(self.height):
       for w in range(self.width):
           r, g, b = self.get(w, h)
           l = int(0.2126 * r + 0.7152 * g + 0.0722 * b)
           self.set(w, h, Colour(l, l, l))

Bitmap.togreyscale = togreyscale


  1. Draw something simple

bitmap = Bitmap(4, 4, white) bitmap.fillrect(1, 0, 1, 2, Colour(127, 0, 63)) bitmap.set(3, 3, Colour(0, 127, 31)) print('Colour:')

  1. Write to the open 'file' handle

bitmap.writeppmp3(ppmfileout) print(ppmfileout.getvalue()) print('Grey:') bitmap.togreyscale() ppmfileout = io.StringIO() bitmap.writeppmp3(ppmfileout) print(ppmfileout.getvalue())


The print statement above produces the following output :

Colour: P3

  1. generated from Bitmap.writeppmp3

4 4 255

  255 255 255   255 255 255   255 255 255     0 127  31
  255 255 255   255 255 255   255 255 255   255 255 255
  255 255 255   127   0  63   255 255 255   255 255 255
  255 255 255   127   0  63   255 255 255   255 255 255

Grey: P3

  1. generated from Bitmap.writeppmp3

4 4 254

  254 254 254   254 254 254   254 254 254    93  93  93
  254 254 254   254 254 254   254 254 254   254 254 254
  254 254 254    31  31  31   254 254 254   254 254 254
  254 254 254    31  31  31   254 254 254   254 254 254

</lang>

R

Library: pixmap

<lang r>

  1. Conversion from Grey to RGB uses the following code

setAs("pixmapGrey", "pixmapRGB", function(from, to){

   z = new(to, as(from, "pixmap"))
   z@red = from@grey
   z@green = from@grey
   z@blue = from@grey
   z@channels = c("red", "green", "blue")
   z

})

  1. Conversion from RGB to grey uses built-in coefficients of 0.3, 0.59, 0.11. To see this, type

getMethods(addChannels)

  1. We can override this behaviour with

setMethod("addChannels", "pixmapRGB", function(object, coef=NULL){

   if(is.null(coef)) coef = c(0.2126, 0.7152, 0.0722)
   z = new("pixmapGrey", object)
   z@grey = coef[1] * object@red + coef[2] * object@green +
       coef[3] * object@blue
   z@channels = "grey"
   z

})

  1. Colour image

plot(p1 <- pixmapRGB(c(c(1,0,0,0,0,1), c(0,1,0,0,1,0), c(0,0,1,1,0,0)), nrow=6, ncol=6))

  1. Convert to grey

plot(p2 <- as(p1, "pixmapGrey"))

  1. Convert back to "colour"

plot(p3 <- as(p2, "pixmapRGB")) </lang>

Ruby

Extending Basic_bitmap_storage#Ruby <lang ruby>class RGBColour

 def to_grayscale
   luminosity = Integer(0.2126*@red + 0.7152*@green + 0.0722*@blue)
   self.class.new(luminosity, luminosity, luminosity)
 end

end

class Pixmap

 def to_grayscale
   gray = self.class.new(@width, @height)
   @width.times do |x|
     @height.times do |y|
       gray[x,y] = self[x,y].to_grayscale
     end
   end
   gray
 end

end</lang>

Tcl

Library: Tk

<lang tcl>package require Tk

proc grayscale image {

   set w [image width $image]
   set h [image height $image]
   for {set x 0} {$x<$w} {incr x} {
       for {set y 0} {$y<$h} {incr y} {
           lassign [$image get $x $y] r g b
           set l [expr {int(0.2126*$r + 0.7152*$g + 0.0722*$b)}]
           $image put [format "#%02x%02x%02x" $l $l $l] -to $x $y
       }
   }

}</lang> Photo images are always 8-bits-per-channel RGBA.

Vedit macro language

Conversion to a grayscale image.

//  Convert RGB image to grayscale (8 bit/pixel)
//    #10 = buffer that contains image data
//  On return:
//    #20 = buffer for the new grayscale image

:RGB_TO_GRAYSCALE:
File_Open("|(VEDIT_TEMP)\gray.data", OVERWRITE+NOEVENT+NOMSG)
#20 = Buf_Num
BOF
Del_Char(ALL)
Buf_Switch(#10)
Repeat(File_Size/3) {
    #9 =  Cur_Char() * 2126
    #9 += Cur_Char(1) * 7152
    #9 += Cur_Char(2) * 722
    Char(3)
    Buf_Switch(#20)
    Ins_Char(#9 / 10000)
    Buf_Switch(#10)
}
Return

Conversion to a color image.

//  Convert grayscale image (8 bits/pixel) into RGB (24 bits/pixel)
//    #20 = buffer that contains image data
//  On return:
//    #10 = buffer for the new RGB image

:GRAYSCALE_TO_RGB:
File_Open("|(VEDIT_TEMP)\RGB.data", OVERWRITE+NOEVENT+NOMSG)
#10 = Buf_Num
BOF
Del_Char(ALL)
Buf_Switch(#20)			// input image (grayscale)
BOF
Repeat(File_Size) {
    #9 =  Cur_Char()
    Char
    Buf_Switch(#10)		// output image (RGB)
    Ins_Char(#9, COUNT, 3)
    Buf_Switch(#20)
}
Return