I have a graphic area with my symbols drawn on the area. I can successfully import a GIF file inside this area with the GIF commands. However, after redrawing my previous graphic area the colors of the previous screen has been changed. How can I avoid this, or how can I bring back my previous colors.
IMPORT of GIF
Is it possible to demonstrate this problem in a short program that we can look at?
Quoted from PaulLaidler Is it possible to demonstrate this problem in a short program that we can look at?
The code is too complex to come here, I am trying to create a simplified code, however, you may see the problem in the following picture:
http://www.intelectri.com/salford/befgif.GIF
I use the routine DRAW_LINE@ to draw lines and so in my graphics.
Here is a simplified code that importing GIF change its original color:
winapp 500000,500000
options(intL)
program TESTGIF
include <windows.ins>
common /hwndo/ hwnd
integer*4 hwnd
integer*4 i,r_x,r_y,r_x1,r_y1,ihandgr,bool
integer*4 posx,POSy,ISTEPCUX,IMAXCUX,ISTEPCUY,IMAXCUY
INTEGER*2 RX,RY,K2,M1C
character*8 filename
INTEGER*4 ERROR1
integer*4 ixor
INTEGER*4 exit_func
external exit_func
call vga@
POSX=10
POSY=10
ISTEPCUX=10
IMAXCUX=20
ISTEPCUY=10
IMAXCUY=20
i=WINDOWS_95_FUNCTIONALITY@()
r_x1 = clearwin_info@('SCREEN_WIDTH')
r_y1 = clearwin_info@('SCREEN_DEPTH')
r_x = r_x1/2
r_y = r_y1/2
! i=WINIO@('%cc&',exit_func)
! i=winio@('%`gr[black,metafile_resize,FULL_MOUSE_INPUT]',r_x,r_y,IHANDGR)
hwnd = clearwin_info@('latest_formatted_window')
! call add_keyboard_monitor@(key_func)
bool=1
call use_approximate_colours@(bool)
call SET_OLD_RESIZE_MECHANISM@
K2=14
CALL DRAW_LINE@(10,10,300,300,K2)
FILENAME='P101.gif'
ixor=0
CALL IMPOGIF(FILENAME,ERROR1,ixor)
call sleep@(4.0)
CALL CLEAR_SCREEN@
rx=ints(r_x)
ry=ints(r_y)
! M1C=0
! CALL FILL_RECTANGLE@(0,0,rx,ry,M1C)
K2=14
CALL DRAW_LINE@(10,10,300,300,K2)
! print *,'hwnd',hwnd,hwndorg
end
!------------------------------------------------------------
SUBROUTINE IMPOGIF(FILENAME,ERROR1,ixor)
include <windows.ins>
COMMON/ FILEDORG1/ FILEDORG
CHARACTER*50 FILEDORG
CHARACTER*(128) FILENAME
INTEGER*4 ERROR1
INTEGER*4 IIMAGE,NIMAGE
INTEGER*4 RES
CHARACTER*80 FILE
COMMON /GRHAND/ IHANDGR
INTEGER*4 IHANDGR
integer*4 ixor
CALL TRIM@(FILENAME)
FILE=FILENAME(1:80)
ERROR1=0
IIMAGE=1
NIMAGE=1
RES=IMPORT_GIF@(FILENAME,IIMAGE,NIMAGE,ERROR1)
call dib_paint@(0L,25L,res,ixor,0L)
IF(ERROR1.NE.0)THEN
PRINT *,'SOME ERROR OCCURED THE gif IS NOT FOUND'
PRINT *,'The file ',FILE, ' is REQUIRED'
ENDIF
RETURN
END
!------------------------------------------------------------
The call to CLEAR_SCREEN@ is erasing the gif image. Just remove it.
Note also that USE_APPROXIMATE_COLOURS@ is for very old graphics displays (I forget the details - VGA or maybe before VGA).
Dear Paul,
The call to clear_screen@ is what I am using to erase the screen and then redraw my graphics again. Indeed this is necessary in my program to refresh the graphic area. Therefore, I can not remove that from my program. This means that if I did not bring the GIF file, redrawing colors was O. right. Is there any other way for me to get back to the previous colors when I redraw my screen. Please see the effect on the WWW link I submitted in my previous quote. On the other hand I can not use other colors instead of USE_APPROXIMATE_COLOURS@ since there are 30 years of networks available in my program, their colors standardize in the program, and can not be changed to other colors. I had not this problem with importing PCX files.
Sharam, if you like try this version. You can resize the window with the mouse, no colour changes appear.
winapp
program test
implicit none
include <windows.ins>
external testgif,u_res
integer*4 j
j = winio@('%ca[Test]%ww[topmost]%bg[black]%sc%pv%`^gr[user_resize,full_mouse_input,'&
//'rgb_colours]',testgif,800L,600L,1L,u_res)
end
!------------------------------------------------------------
INTEGER FUNCTION TESTGIF()
include <windows.ins>
integer*4 error1
character*128 filename
call draw_line_between@(10,10,300,300,rgb@(130,90,40))
filename='P101.gif'
call IMPOGIF(filename,error1)
call sleep@(1.0)
call draw_line_between@(10,10,300,300,rgb@(130,90,40))
testgif = 1
end
!------------------------------------------------------------
SUBROUTINE IMPOGIF(filename,error1)
include <windows.ins>
character*128 filename
integer*4 res,error1
c_external import_gif@ '__import_gif'(STRING,VAL,REF,REF) : integer*4
common /aaa/ res
res = import_gif@(filename,1L,1L,error1)
call dib_paint@(10L,25L,res,0L,0L)
return
end
!------------------------------------------------------------
INTEGER FUNCTION U_RES()
include <windows.ins>
integer*4 k,res
common /aaa/ res
k = clearwin_info@('graphics_resizing')
if (k == 1) then
k = dib_paint@(10L,25L,res,0L,0L)
call draw_line_between@(10,10,300,300,rgb@(130,90,40))
end if
u_res = 1
end
Wilfried
If you must 'clear the screen' then you must also re-draw the gif image afterwards.
GIF file functions have predefined color palette which can be changed by the user. Clearwin+ is working with such a fixed color palette.
Like in other graphics programs it might be, that a call to GIF functions (e.g. 'save as') changes or overwrites your color palette. Check the number of colors in your GIF input file; perhaps you have there only 8 colors. This might change your color palette. It might help to change your GIF import file to 256 colors. If not, try to convert your GIF file logo to a PNG file. That has definitely a wide color palette.
Erwin
... or load the GIF into a %gr region with the rgb_colours option like in my example above - then, the GIF graphics are converted into the 24-bits RGB colour space. As you can also see in my example, I always used RGB colours, for instance in the draw_line_between@ routine.
Whenever you resize the window, the GIF graphics is redrawn without any modification of colours (done by the U_RES function and within that by the dib_paint@ function) .
Wilfried
Try .png format and all the colour palette problems will go away. John
Thank you all. The problem has been overcome with using DRAW_LINE_BETWEEN@ instead of DRAW_LINE@ . However, I had to go to RGB colors. This takes a lot of modifications inside my program, however, the colors are much more brighter and I decided to use RGB colors in my program.
Thanks all again.
Sharam,
RGB colours are the way forward - the other options take you back 20 years, and are computer archaeology!
Eddie