Silverfrost Forums

Welcome to our forums

list view control with icon list

11 Apr 2019 10:12 #23478

From time to time my program crashes when I open a dialog box with a %`lv control that uses an icon list. I cannot reproduce the problem with a certain procedure and it occurs only every few days. The error message looks like :

Access violation (c0000005) at address 7ffb71e629e7

Within file COMCTL32.DLL In HIMAGELIST_QueryInterface at address 87 In ImageList_GetIconSize at address 4D In SizeBoxHwnd at address FDB In Ordinal20 at address 1CBD6 In ImageList_Add at address 6E5 In Ordinal342 at address 2A8C In Ordinal342 at address 4E2 In CallWindowProcW at address 4DD Within file USER32.dll In CallWindowProcW at address 8B In DefSubclassProc at address 2A5

11 Apr 2019 12:51 #23479

Ralf

None of the functions in the list are internal ClearWin+ functions so I would need more information to find the source of the failure. The functions are all within the Windows API.

11 Apr 2019 3:21 #23482

Paul,

I was afraid of that. Unfortunately I am not able to reproduce this intended, which makes it probably impossible to solve. The only additional information that I can provide is part of the code:

      iw=winio@('  %pv%^`lv[single_selection,full_row_select,show_selection_always,user_font]  &',             &
                  600,200,items,nitems,iselect,iview, 'icon1,icon2,icon3,icon4,icon5,icon6,icon7',sort_list)

but I think this would'nt give you any hint... I cannot even say if this is a 64bit Problem, but so far it only appeared in the 64bit Version of my code.

11 Apr 2019 3:45 #23483

Ralf

If you are able to provide a working sample (with the code) then I could at least trace through the bits of ClearWin+ that you are using. That might give me some clues.

12 Apr 2019 6:16 #23485

Paul,

I am sorry, but unfortunately this is not possible. Our code (a FE pre-and postprocessor) is a quite complex program with more than 200000 lines of code and the problem occurs only with quite large models from our customers which are confidential. The only solution that I can see so far is to remove the icons from the listviews.

12 Apr 2019 6:35 #23486

Ralf

All I would need would be something like your extracted code above but expanded into a simple working dialog.

14 Apr 2019 11:07 #23494

Quoted from John-Silver (I'll have to source an oxygen mask ready to stop me from passing out from laughing when you tell me 😉 )

John, I am not sure of your pre-conceived view of 'large' Any problem that exceeds the size that is allowed for in the particular part of the program will be too big, especially when stack usage has been included.

My finite element program is typically limited to 400,000 nodes, but have worked with up to 10 million nodes for some special applications. (I was surprised by the ease of use and speed of my large application models.) Some of my modelling that is much smaller have presented size limitations and overflowed Clearwin+ capabilities.

When moving to 64-bit, it is important to assess resource limitations, especially when using multiple virtual windows. Issues of heap vs stack, physical memory available and extrapolating 32-bit clearwin usage concepts to 64-bit problems needs to be carefully adapted.

Ralf, Your problem may be related to memory usage, so if you are able to run your large models, I would recommend including some resource usage reports, including memory usage as below. Task manager is also a useful indicator. There are also API routines for reporting stack size and usage (I can't find examples at the moment)

 module memparam
     integer*4, parameter :: million = 1000000
     logical   :: bit_64 = .true.                  ! change for 32-bit or 64-bit compile
     integer*8 :: one_Mb = 2**20                   ! size of 1 Mb 
     integer*8 :: one_Gb = 2**30
 end module memparam

   PROGRAM BIG 
  use memparam
!
      integer*4, parameter :: n = 50*million
!
      REAL*8, allocatable :: A(:),B(:),C(:)         !a 
      REAL*8, allocatable :: D(:),E(:),F(:)         !a 
      REAL*8, allocatable :: X(:),Y(:),Z(:)         !b 
      INTEGER*4 J, stat
      integer*4 addr(2)
      integer*8, external :: jloc
!      
      call report_memory_usage ('FTN95_64_Version : start of usage')
!
      allocate ( A(n), stat=stat )
      call report_memory_usage ('FTN95_64_Version : A allocated')
      if ( stat == 0 ) then
!z        A(:)=(/(j,j=1,n)/)
        do j = 1,n
          A(j) = j
        end do
        J = n 
        call Gb_loc (A, addr)
        write (*,11) 'A allocated at', jloc(A), addr, A(j)
      else
        write (*,12) 'A NOT allocated : stat=', stat
      end if
!
      allocate ( B(n), stat=stat )
      call report_memory_usage ('FTN95_64_Version : B allocated')
      if ( stat == 0 ) then
        B = A+1   !a
        call Gb_loc (B, addr)
        write (*,11) 'B allocated at', jloc(B), addr, B(j)
      else
        write (*,12) 'B NOT allocated : stat=', stat
      end if
!
      allocate ( C(n), stat=stat )
      call report_memory_usage ('FTN95_64_Version : C allocated')
      if ( stat == 0 ) then
        C = A+2   !a
        call Gb_loc (C, addr)
        write (*,11) 'C allocated at', jloc(C), addr, C(j)
      else
        write (*,12) 'C NOT allocated : stat=', stat
      end if
!
      allocate ( d(n), stat=stat )
      call report_memory_usage ('FTN95_64_Version : D allocated')
      if ( stat == 0 ) then
        D = A+3   !a
        call Gb_loc (D, addr)
        write (*,11) 'D allocated at', jloc(D), addr, D(j)
      else
        write (*,12) 'D NOT allocated : stat=', stat
      end if
!

Where is the larger post size ???

14 Apr 2019 11:11 #23495

program ctd ! allocate ( e(n), stat=stat ) call report_memory_usage ('FTN95_64_Version : E allocated') if ( stat == 0 ) then E = A+4 !a call Gb_loc (E, addr) write (,11) 'E allocated at', jloc(E), addr, E(j) else write (,12) 'E NOT allocated : stat=', stat end if ! allocate ( f(n), stat=stat ) call report_memory_usage ('FTN95_64_Version : F allocated') if ( stat == 0 ) then F = A+5 !a call Gb_loc (F, addr) write (,11) 'F allocated at', jloc(F), addr, F(j) else write (,12) 'F NOT allocated : stat=', stat end if ! allocate ( X(n), stat=stat ) call report_memory_usage ('FTN95_64_Version : X allocated') if ( stat == 0 ) then X = A+6 !a call Gb_loc (X, addr) write (,11) 'X allocated at', jloc(X), addr, X(j) else write (,12) 'X NOT allocated : stat=', stat end if ! allocate ( y(n), stat=stat ) call report_memory_usage ('FTN95_64_Version : Y allocated') if ( stat == 0 ) then Y = A+7 !a call Gb_loc (Y, addr) write (,11) 'Y allocated at', jloc(Y), addr, Y(j) else write (,12) 'Y NOT allocated : stat=', stat end if ! allocate ( Z(n), stat=stat ) call report_memory_usage ('FTN95_64_Version : Z allocated') if ( stat == 0 ) then Z = A+8 !a call Gb_loc (Z, addr) write (,11) 'Z allocated at', jloc(Z), addr, Z(j) else write (,12) 'Z NOT allocated : stat=', stat end if 11 format (/a,' LOC =',i12,' or ',i3,':',i10,' val=',f0.1) 12 format (/a,1x,i0) ! END PROGRAM BIG

    real*8 function Gb ( bytes )
  use memparam
      integer*8 :: bytes
!
      Gb = dble (bytes) / dble (one_Gb)
    end function Gb

    real*8 function Mb ( bytes )
  use memparam
      integer*8 :: bytes
!
      Mb = dble (bytes) / dble (one_Mb)
    end function Mb

    integer*8 function jloc (address)    ! wirks for both 32-bit and 64-bit
  use memparam
      real*8    address(*)
      integer*4 aa(2)
      integer*8 bb
      equivalence (aa,bb)
!
      if ( bit_64 ) then
        bb    = loc (address)
      else
        bb = 0
        aa(1) = loc (address)
      end if
      jloc  = bb
    end function jloc

    subroutine Gb_loc (address, addr)
  use memparam
      REAL*8    address(*)
      integer*4 addr(2)
!
      integer*8 bb
      integer*8, external :: jloc
!
      bb      = jloc (address)
      addr(1) = bb / one_Gb
      addr(2) = mod (bb, one_Gb)
    end subroutine Gb_loc

    subroutine report_memory_usage (string)
!
      character string*(*)
!
     stdcall GlobalMemoryStatusEx 'GlobalMemoryStatusEx'(REF):logical 
!     logical, external :: GlobalMemoryStatusEx
!
       integer*4 :: dwLength
       integer*4 :: dwMemoryLoad
       integer*8 :: ullTotalPhys
       integer*8 :: ullAvailPhys
       integer*8 :: ullTotalPageFile
       integer*8 :: ullAvailPageFile
       integer*8 :: ullTotalVirtual
       integer*8 :: ullAvailVirtual
       integer*8 :: ullAvailExtendedVirtual
     integer :: mdata(16) 
14 Apr 2019 11:13 #23496

and more integer :: mdata(16) equivalence ( mdata( 1), dwLength ) equivalence ( mdata( 2), dwMemoryLoad ) equivalence ( mdata( 3), ullTotalPhys ) equivalence ( mdata( 5), ullAvailPhys ) equivalence ( mdata( 7), ullTotalPageFile ) equivalence ( mdata( 9), ullAvailPageFile ) equivalence ( mdata(11), ullTotalVirtual ) equivalence ( mdata(13), ullAvailVirtual ) equivalence ( mdata(15), ullAvailExtendedVirtual ) integer8 :: lastAvailPhys = 0 real8, external :: Gb

     dwLength = 64 
    
     if (GlobalMemoryStatusEx(mdata)) then 
    
       write (*,11) 'Memory report at ', string, ' Mem_avail= ', ullAvailPhys
    
       print *,  'Percentage of physical memory in use        ', dwMemoryLoad            
       print 10, 'Amount of actual physical memory            ', Gb (ullTotalPhys)
       print 10, 'Amount of physical memory available         ', Gb (ullAvailPhys)
       print 10, 'Committed memory limit                      ', Gb (ullTotalPageFile)
       print 10, 'Amount of memory current process can commit ', Gb (ullAvailPageFile)
       print 10, 'Size of virtual address space               ', Gb (ullTotalVirtual)
       print 10, 'Amount of unreserved/uncommitted memory     ', Gb (ullAvailVirtual)
       print 10, 'Change in physical memory available         ', Gb (ullAvailPhys-lastAvailPhys)
    
      lastAvailPhys = ullAvailPhys
    
     else 
       print*,'Report Memory Failed ', string  
     end if 
    
  10 format(1x,a,f0.3) 
  11 format (/a,a,2x,a,B'---,---,---,--#')
!  11 format (/a,a,2x,a,i0)
     
    end subroutine report_memory_usage
Please login to reply.