Silverfrost Forums

Welcome to our forums

GIF file from %og graphics ?

21 Oct 2014 7:18 #14904

Thanks Wilfried,

now it's perfect! Here my final source code.

    INTEGER FUNCTION SaveOpenGL_Bitmap () 
    IMPLICIT NONE
    INCLUDE  <clearwin.ins>
    INCLUDE  <opengl.ins>
    CHARACTER    GIF_FileName*64
    GIF_FileName = 'Graphics.gif'
    CALL OpenGL_To_GIF (GIF_FileName)
    SaveOpengl_Bitmap = 2
    RETURN
    END FUNCTION SaveOpenGL_Bitmap


    SUBROUTINE OpenGL_To_GIF (GIF_FileName)
    IMPLICIT NONE
    INCLUDE  <clearwin.ins>
    INCLUDE  <opengl.ins>

    CHARACTER    GIF_FileName*(*)

    INTEGER      I, J, K, iSizeX, iSizeY, iBit, iErr, iBMP_Handle, Koff, Kount, MA
    CHARACTER*1, ALLOCATABLE :: ImageData(:)
    CHARACTER*1, ALLOCATABLE :: ImageDIB(:,:,:) 
    CHARACTER    BMP_FileName*32
    LOGICAL      EXI

    iSizeX = clearwin_info@ ('OPENGL_WIDTH')
    iSizeY = clearwin_info@ ('OPENGL_DEPTH') 

    ALLOCATE (ImageData(3*(iSizeX+3)*iSizeY))
    ALLOCATE (ImageDIB(3,iSizeX,iSizeY))
    ImageData = ' ' 
    ImageDIB  = ' ' 

    CALL glReadPixels (0, 0, iSizeX, iSizeY, GL_RGB, GL_UNSIGNED_BYTE, ImageData) 
    Koff  = mod (iSizeX, 4) 
    Kount = 0 
    DO J= 1, iSizeY 
        DO I= 1, iSizeX 
            DO K= 1, 3 
                Kount = Kount + 1 
                ImageDIB(K, I, iSizeY-J+1) = ImageData(Kount) 
            ENDDO 
        ENDDO 
        Kount = Kount + Koff 
    ENDDO 

    BMP_FileName = 'OpenglTemp37168.bmp'

    INQUIRE (FILE= BMP_FileName, EXIST= EXI) 
    IF (EXI) CALL ERASE@ (BMP_FileName, iErr)
    
    CALL Put_DIB_Block@ (BMP_FileName, ImageDIB, iSizeX, iSizeY, 0, 0, iSizeX, iSizeY, 24, iErr) 
    CALL Get_DIB_Size@ (BMP_FileName, iSizeX, iSizeY, iBit, iErr)
    iBMP_Handle = Import_BMP@ (BMP_FileName, iErr)
    MA = Create_Graphics_Region@ (2L, iSizeX, iSizeY)
    MA = Select_Graphics_Object@ (2L) 
    MA = DIB_Paint@ (0, 0, iBMP_Handle, 0, 0) 
    MA = Export_Image@ (GIF_FileName)
    MA = Delete_Graphics_Region@ (2L)
    MA = MA
    CALL ERASE@ (BMP_FileName, iErr)

    RETURN
    END SUBROUTINE OpenGL_To_GIF

Of course, the GIF_FileName has to be set individually.

Erwin

21 Oct 2014 10:50 #14906

MA=MA?

I suspect that with all the error codes and function return codes, you will need a lot of extra code to handle all possible error conditions and exit gracefully!

Can I suggest using TEMP_FILE@ and SET_SUFFIX@ (See the FTN77 library) to give you a unique temporary BMP filename?

Eddie

21 Oct 2014 3:38 #14908

I made a few more tests to convert BMP to GIF and I found a funny behaviour of the export_gif function. Maybe this is of interest for Paul?

      winapp 
      program test 
      implicit none

      c_external bmp_imp '__import_bmp'(STRING,REF) : integer*4
      c_external gif_exp '__export_gif'(VAL,STRING,REF)

      integer*4     hdl,rtcode
      character*256 file

      file = 'graphics.bmp'//char(0)
      hdl  = bmp_imp(file,rtcode)
      file = 'graphics.gif'//char(0)
      call gif_exp(hdl,file,rtcode)
      end

Results:

(1) Sometimes gif_exp returns 11 like previously reported by Erwin. The output file is created but empty. (2) Sometimes the program breaks down (for instance this happened with some 8-bit grey-scale BMPs) (3) Sometimes it works perfectly (!!), the GIF is created.

Regards - Wilfried

22 Oct 2014 7:25 #14912

I keep forgetting what I can and can't do with Device Independent Bitmaps. Having both array and handle addresses is confusing, while they don't appear to be easily related.

Erwin's approach looks to work, but why do we need to create a temporary .bmp file ?

His approach is:

Get the size of the Opengl image Create a DIB array for that size Interrogate the Opengl region and populate the ImageDIB export ImageDIB to a .bmp file with Put_DIB_Block@ Interrogate the .bmp file to get it's size Import the .bmp file to a DIB handle using Import_BMP@ Create a graphics region of the same size with Create_Graphics_Region@ select this graphics region with Select_Graphics_Object@ copy the DIB handle to this graphics region with DIB_Paint@ export the graphics region to file using Export_Image@ Tidy up all the left overs.

Why can't we copy the DIB array direct to the Graphics region ?

Export_Image@ is now very flexible as it supports .png, .jpg, .jpeg, .bmp, .gif, .emf, and .pcx.

An alternative may be to not use DIB routines at all, but a temporary RGB_colour_array then 'paint' it to the new selected graphics object using:

Get the size of the Opengl image Create an array for that size to store the pixel values. Interrogate the Opengl region and populate the colour array Create a graphics region of the same size with Create_Graphics_Region@ select this graphics region with Select_Graphics_Object@ Populate the graphics region with either Draw_Point@ or Draw_Line_Between@, scanning each horizontal line where the same colour is repeated. export the graphics region to file using Export_Image@ Tidy up all the left overs.

I have found Draw_Line_Between to be an efficient approach where only a small colour palette is used. With a 1920x1080 resolution image, this is 2 million calls to Draw_Point, which was once quite slow. You need to test.

This is the approach I have used for my 'hidden line removal' approach, where I keep a colour array(horz,vert) as character1 colour index (255 colours) and depth array(horz,vert) as a real4 active depth of each pixel. When complete, I paint this array to the selected graphics object (%gr or virtual) then direct to .png file. ( I support up to 3072 x 2304 virtual image which is 35 mb for me to store )

I would expect the temporary array is needed as it may be difficult (inefficient) to switch between the opengl region and the Select_Graphics_Object as an active region.

Anyone tried these alternatives ?

John

22 Oct 2014 12:44 #14914

John,

The approaches given do work, but may not be the most efficient. I'd like to see a working version of your proposal for comparison of run times. The intermediate bitmap step does seem to be ridiculous, I agree. However, it mainly uses existing Clearwin+ routines that require little knowledge of the structure of any particular format.

I think that for a limited palette, OpenGL (%og) is over-complicated relative to %gr, but often OpenGL is used because of complicated shading, in which case the palette won't be small - simple graphics with a few areas of solid colour, lines and text are very easy with %gr.

Eddie

22 Oct 2014 2:47 #14915

The following code shows the problem. First, a 24-bits image (800 x 600 pixels) is created and saved as BMP, you can control this with any image viewer. Then, this BMP is imported by import_bmp and should be exported with export_gif. As far as I found out unto now, export_gif cannot handle 24-bits images:

      winapp
      program test
      implicit none
      include <windows.ins>

      integer*4      i,j,A
      character*1    image(1450000)
      character*256  ifile,ofile

      c_external bmp_imp '__import_bmp'(STRING,REF) : integer*4
      c_external gif_exp '__export_gif'(VAL,STRING,REF)

      ifile = 'test.bmp'//char(0)
      ofile = 'test.gif'//char(0)

c     create 24-bits test image

      do i = 1,600
        A = (i-1)*2400
        do j = 1,2400,3
          image(A+j  ) = char(mod(j,255))
          image(A+j+1) = char(mod(i,255))
          image(A+j+2) = char(mod(i+j,255))
        end do
      end do

c     off-screen graphics & export to BMP

      j = create_graphics_region@(4L,800L,600L)
      j = select_graphics_object@(4L)
      call display_dib_block@(0,0,image,800L,600L,0,0,800L,600L,0,0,i)
      if (i == 0) j = export_image@(ifile)
      j = delete_graphics_region@(4L)

c     import of BMP and export to GIF

      A = bmp_imp(ifile,i)
      if (i == 0) call gif_exp(A,ofile,i)   !! here the program failes
      end

Wilfried

22 Oct 2014 9:31 #14916

Wilfried, i'd also add the deallocate to your first code

22 Oct 2014 10:28 #14917

Wilfred,

.gif uses a fixed 256 colour palette. It chooses the 'closest' colour to it's available palette. To overcome this .png format can be used, which is what I lobbied for. Just replace .gif with .png and you will see an improvement. I now use .png for all my graphics dumps. .gif is suitable when there are only a few colours, as the resulting file is very compact.

Eddie may have a valid point, that opengl may use a very large palette of colours, which would need to be stored as RGB in the temporary array.

DIB could be much more useable if there were a few basic routines to allow transfer between DIB arrays, DIB handles and Graphics_Objects.

John

23 Oct 2014 1:19 #14919

Dan and John,

I don't use GIF in my own software (only BMP, JPEG and TIFF). I only had a little bit of time yesterday and tried to find out why the export_gif function has that funny behaviour.

In my software I use functions from a friend of mine, written in C, and also sometimes parts of the FreeImage library.

Wilfried

23 Oct 2014 2:34 #14921

My line graphics have about 20 to 30 different colors. Therefor GIF-files are perfect.

I extended my subroutine a little between DIB_Paint@ and Delete_Graphics_Region@ to allow a copy of the graphics to the paste buffer, and found a curious situation:

    MA = DIB_Paint@ (0, 0, iBMP_Handle, 0, 0) 

    CALL  DRAW_RECTANGLE@ (4, 4, iSizeX-5, iSizeY-5, RGB@( 84,252, 84))

    IF (GIF_FileName .EQ. ' ') THEN
       MA = GRAPHICS_TO_CLIPBOARD@ (0, 0, iSizeX-1, iSizeY-1)
    ELSE
       MA = Export_Image@ (GIF_FileName)
    ENDIF

    MA = Delete_Graphics_Region@ (2L)

DRAW_RECTANGLE@ creates a box with distance of four pixels from all edges. The graphic file from Export_Image@ is correct; for the paste buffer I have to use the parameters above to have a correct image in the buffer !? A bug?

Erwin

23 Oct 2014 8:33 #14923

Quoted from DanRRight Wilfried, i'd also add the deallocate to your first code

Sorry I meant Erwin but wrote Wilfried, I'd add deallocate to your code, few large files repeated many times may take huge chunk of RAM making a memory leak

24 Oct 2014 7:31 #14925

Thank Dan,

according to FORTRAN rules local allocated memory has to be de-allocated automatically after return from the subroutine. However, it does not work - I checked it. Memory usage will be increased after each call.

I have to check my other programs as well.

Erwin

24 Oct 2014 10:03 #14927

Paul,

as you see from my last post, size of the occopied memory of my program is increasing after each call of the subroutine. Of course I will deallocate the arrays.

I tried the same when calling the subroutine with the parameters (...,iSizeX,iSizeY) and use automatic allocation like in the code from John Horspool, or as shown below. The occupied memory is still increasing after each call of the subroutine.

 PROGRAM MemTest1
    IMPLICIT   NONE
    INTEGER*4  I, J, K
    DO I= 1, 100000
       J = 2000
       K = 2000
       WRITE(*,'(i10)') I
       CALL Sub1 (J, K) 
    ENDDO
    END PROGRAM MemTest1

    SUBROUTINE Sub1 (M, N)
    IMPLICIT   NONE
    INTEGER*4  M, N
    INTEGER*4  Large(M,N)
    Large(1,1) = 123456789
    Large(M,N) = Large(1,1)
    RETURN
    END  SUBROUTINE Sub1

In the example above everything works fine as well if I use allocate without deallocate. There seems to be a terrible bug for larger code ?!

Erwin

24 Oct 2014 12:42 #14928

Thanks. I have logged this for investigation.

25 Oct 2014 11:14 #14931

Paul,

after introduction of an deallocate, the occupied memory of my program is still increasing after each creation of a GIF file.

Therefore I reduced the program to a minimum which I would like to send to you by email for further evaluation (no exe-file).

Erwin

25 Oct 2014 11:30 (Edited: 25 Oct 2014 12:00) #14932

I finally had time to look at what Wilfred posted last Thursday. The following change, using FTN95 Ver 7.10.0 works ok, at least up to exporting the 3 images. I did not look at the BMP import, as I am not familiar with these routines. As I have demonstrated, export_image@ works well. I think support for .png was introduced recently in Ver 6.35; not sure when .gif was supported. Hopefully if this example works for you, the difference between .gif and .png shows the limited colour palette. winapp program test implicit none include <windows.ins>

       integer*4      i,j,A 
       character*1    image(1450000) 
       character*256  ifile,ofile, gfile,pfile

       c_external bmp_imp '__import_bmp'(STRING,REF) : integer*4 
       c_external gif_exp '__export_gif'(VAL,STRING,REF) 

       ifile = 'test.bmp'//char(0) 
       ofile = 'test.gif'//char(0) 
       gfile = 'test_02.gif'
       pfile = 'test_02.png'

!    create 24-bits test image 

       do i = 1,600 
         A = (i-1)*2400 
         do j = 1,2400,3 
           image(A+j  ) = char(mod(j,255)) 
           image(A+j+1) = char(mod(i,255)) 
           image(A+j+2) = char(mod(i+j,255)) 
         end do 
       end do 

!    off-screen graphics & export to BMP 

       j = create_graphics_region@(4L,800L,600L) 
       j = select_graphics_object@(4L) 
       call display_dib_block@(0,0,image,800L,600L,0,0,800L,600L,0,0,i) 
       if (i == 0) then
         j = export_image@ (ifile) 
         j = export_image@ (gfile) 
         j = export_image@ (pfile) 
       end if
       j = delete_graphics_region@(4L) 

!    import of BMP and export to GIF 

       A = bmp_imp(ifile,i) 
       if (i == 0) call gif_exp(A,ofile,i)   !! here the program failes 
       end
25 Oct 2014 11:59 #14933

Erwin,

I am trying to understand your memory leak problem. I can't identify which code sample has the problem. If it relates to reading a .bmp file into a DIB handle, then there is memory associated with the handle, which has to be released. I have also seen some memory leak associated with some .gif routines, but I recall this was not a large amount of memory. I think Fortran's use of ALLOCATE is more robust than C's malloc, as the deallocate is now implicitly required.

In the production version of your code, how many .gif files do you need to create ?

John

25 Oct 2014 12:26 #14935

If deallocation works by default (or should work) when exit the sub - great, i did not check that lately because having eternal problem with lack of memory i always deallocate. As to how many files - we sometimes output 1000 files for making movies of process dynamics

25 Oct 2014 1:23 #14936

Yes. As I recall, the standard requires an automatic DEALLOCATE on return.

26 Oct 2014 10:52 #14939

Dan, John,

I tried of course to return the memory by setting the DIB handle to zero und calling window_update@. There was no enhancement.

The purpose of the GIF files in this program is to rotate the graphics and make series of GIF files and play it later. For several 3D point cloud objects you can recognize the structure only, when the object will be rotated. Because this is a new feature in the program, I do not know how many shots will be made.

In the other 5 graphics programs - using %gr - the memory is as well increasing but the amount is only 30 to 40 KB per shot and therefore neglectable.

Erwin

BTW: I have sent the source to Paul.

Please login to reply.