Grayscale image

From Rosetta Code
Revision as of 17:57, 19 February 2009 by rosettacode>ShinTakezou (fortran)
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 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; </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.

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 ;
\ 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. 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

 gray = animage
 animage = gray
 call output_ppm(an_unit, animage)</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>

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