W$SAVE_IMAGE
The W$SAVE_IMAGE routine saves the image pointed by a bitmap handle into a regular disk file. The save process allows you to convert the image to a different format and set some attributes like quality and transparency.
Syntax:
 CALL "W$SAVE_IMAGE" USING bitmapHandle
                           fileName
                          [WSAVE-OPTIONS]
                    GIVING returnCode
Parameters:
bitmapHandle
USAGE HANDLE
It specifies an handle of an existing image.
fileName
PIC X(n)
Specifies the name of a regular disk file that will store the saved image.
WSAVE-OPTIONS
Group Item
Structure that allows you to customize the image format, quality and attributes. It’s defined in iscobol.def as follows:
 
01 wsave-options.
   03 wsave-format pic x(1).  
      88 wsave-png values "P"" ".
      88 wsave-bmp value  "B".
      88 wsave-gif value  "G".
      88 wsave-jpg value  "J".
   03 wsave-other.
      05 wsave-quality pic 9(10comp-x.
      05 wsave-transparency redefines wsave-quality.
         07 filler pic 9(1comp-x.
            88 no-transparency value 0 false 1.
         07 wsave-transparent-color pic 9(9comp-x.
   03 wsave-client-server pic x.
      88 wsave-server values "S"" ".
      88 wsave-client value  "C".
 
wsave-format
Image format between BMP, GIF, JPG and PNG. By default PNG is used.
 
wsave-quality
Image quality value. The valid range is from 0 (best compression, lower quality) to 100 (no compression, best quality). It’s evaluated only for the JPG format.
 
wsave-transparency
Activates the transparency and identifies the RGB of the transparent color. wsave-transparent-color can be calculated as follows: (RED * 65536) + (GREEN * 256) + BLUE. It’s evaluated only for the PNG and GIF formats.
 
wsave-client-server
Specifies if the image must be saved server side or client side in a thin client environment. By default the image is saved on the same machine where the runtime system is running, so server side in thin client.
Return code:
returnCode can be any numeric data item and provides additional information:
0
Operation failed.
1
Operation successful.
Example:
Example - Load a BMP file and save it as JPG
working-storage section.
copy "isgui.def".
copy "iscobol.def".
77 hbmp handle.
 
procedure division.
main.
     call "w$bitmap" using wbitmap-load, "src.bmp"giving hbmp.
     initialize wsave-options.
     set wsave-jpg to true.
     move 75 to wsave-quality.
     call "w$save_image" using hbmp, "dest.jpg", wsave-options.
     goback.