Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

ListView Not Working in Intel Paralles Studio 2018

salim__karen
Beginner
975 Views

 

Hello, and thanks in advance, is there a compatibility compilation propertie that should be added to ensure the gui funcionalities on a ivf 2011 program?

thanks,

0 Kudos
1 Solution
Steve_Lionel
Honored Contributor III
975 Views

I spent the past couple of days converting an ancient (1994!) MSDN ListView C sample to Intel Fortran. It mostly works - in that the ListView displays properly. Some other aspects of the program don't work for reasons I haven't yet figured out, and it doesn't help that the C version doesn't work at all. But it works enough to tell me that display of the listview is ok.

There is allegedly a simpler Listview sample in the current Windows SDK, but it won't install for me and I can't figure out why.

I may continue playing with this when I have the time. It's an interesting example. Here's a screenshot.

Screenshot_1.jpg

View solution in original post

0 Kudos
13 Replies
Steve_Lionel
Honored Contributor III
975 Views

You're going to have to provide a lot more information - ideally a small but complete sample program (a ZIP of a complete project would be best) and an explanation of the behavior you find incorrect. There is no compiler option related to Windows GUI support. Typically a Windows GUI program would be built as a "Windowing Application" project type with a WinMain entry point.

I'm also a bit confused by your referring to "ivf 2011" and "Parallel Studio 2018". Which are you using?

0 Kudos
salim__karen
Beginner
975 Views

Hi Steve! Thanks for the reply,

I have a program compiled with Visual Studio 2010 and Fortran 2011.  When upgrading to Visual Studio 2017 and Fortran compiler 2018, the program runs ok but the listview functionality is not displaying its columns like it used to show. Is there a Run-time configuration or is a code difference that we should address?

I am attaching the before/after images.

Before.png

after.png

0 Kudos
Steve_Lionel
Honored Contributor III
975 Views

Can you show us a small but complete example? I'm not aware of anything you should have needed to change. I've never tried the ListView control, though.

0 Kudos
salim__karen
Beginner
975 Views

 

Hey, thanks again for the reply and help

Here is where the report is updated:

Subroutine Update
 
! INit code
 
   lret = InitLVColumns ()
 
!some code
 
   i = SendMessage (hwndLV, LVM_SETITEMCOUNT, ipar, LVSICF_NOINVALIDATEALL)
 
   If (RepDef.szRep * RepDef.NCol < 3000) Then
      Call WndRep_ColumnsWidth (.true.)
   EndIf
 
   End Subroutine Update
 
And here is where de columns are created:
 
   Logical Function InitLVColumns ()
 
! Init Code
 
   ! Initialize the LVCOLUMN structure. 
   col.mask = ior(LVCF_FMT, ior(LVCF_SUBITEM, ior(LVCF_TEXT, LVCF_WIDTH)))
   col.fmt = LVCFMT_LEFT
   col.cx = 80
   !col.cx = (rcList.right - rcList.left)/7
   Do i = 1, RepDef.NCol
      col.PSZTEXT = loc(RepDef.ColName(i))
      col.iSubItem = i-1
      ipar = i-1
      ret = SendMessage (hwndLV, LVM_INSERTCOLUMNA, ipar, loc(col))
      ret = SendMessage (hwndLV, LVM_SETCOLUMNA, ipar, loc(col))
      If (ret == -1) Then
         WndRep_InitLVColumns = .false.
         Return
      EndIf
   EndDo
   WndRep_InitLVColumns = .true.
  
 
   End Function InitLVColumns

 

The listview is a virtual list that displays with 

 Case (LVN_GETDISPINFO)
 
            p2 = lparam
            If (IAnd(LVDispInfo.item.mask, LVIF_TEXT)) Then
 
               iSb = LVDispInfo.item.iSubItem
               iIt= RepIdx(LVDispInfo.item.iItem + 1)
 
               If (iSb == 0) Then
                ............
               ElseIf (iSb > 0) Then
              ............
               EndIf
 
            EndIf
 
the LVColumn it doesn't return true 
and the
but LVDispInfo.Item.iSubitem also is always zero with the new compiler 2018. Can´t figure it out why is not working.
thanks,
 
 
0 Kudos
ZlamalJakub
New Contributor III
975 Views

I had problems with ListView and 2018 compiler too. Problem was caused by wrong integer type of callback functions I have used to cubclass window procedures. My code was 15 years old and I did not care about correct data types.

Correct type is integer(LRESULT)

I hope it helps.

Are you compiling 64bit or 32bit application?

 

0 Kudos
Steve_Lionel
Honored Contributor III
975 Views

Please attach a ZIP of a small but complete example that shows the problem. We can't do much with snippets of code.

0 Kudos
Steve_Lionel
Honored Contributor III
976 Views

I spent the past couple of days converting an ancient (1994!) MSDN ListView C sample to Intel Fortran. It mostly works - in that the ListView displays properly. Some other aspects of the program don't work for reasons I haven't yet figured out, and it doesn't help that the C version doesn't work at all. But it works enough to tell me that display of the listview is ok.

There is allegedly a simpler Listview sample in the current Windows SDK, but it won't install for me and I can't figure out why.

I may continue playing with this when I have the time. It's an interesting example. Here's a screenshot.

Screenshot_1.jpg

0 Kudos
salim__karen
Beginner
975 Views

hi Steve

Thanks again !! And I’m glad that works in C that’s indicates that should work for me too. I’m still investigating.As the code is large and we intend to turn it 64b, I am hopping that the integer  handle as Zlamal mentioned could be a good start. I should try a small example to see if all turns ok. As for now nothing is reallying working. 

I’ll post here if I can get this right for the small case. Thanks again and let me know if you have some other issue that I should address.

 

0 Kudos
Steve_Lionel
Honored Contributor III
975 Views

The version I have mostly working is Fortran. The C version throws many errors from the C compiler, and while the Listview displays, the contents are all random characters. Initially the C code would not build at all, but I managed to bypass the severe errors. I am not all that good in C and I didn’t feel like trying to track down all the complaints.

The parts that don’t work are the column sorting (I can see my compare routine being called, but nothing gets sorted), and the two alternate view modes for the list. If you think it will be helpful I’ll upload a zip of the project.

 

0 Kudos
Steve_Lionel
Honored Contributor III
975 Views

I've attached my Fortran version of the ListView sample. Now everything works except the sorting. I can see that the sort happens, but the items continue to be displayed in their original order. The only other ListView samples I can find, including the one at Github where Microsoft moved all the samples, use a different API that has no bearing on the message-based one.

I also attached the C version. I don't trust all the comments in the C code, as I found some of them are inaccurate.

0 Kudos
salim__karen
Beginner
975 Views

Hi Steve, 

Thanks for  the archive! I`ll let you now if i figure it out my problem here. As I said it is a large code and we intend to migrate. 

 

 

0 Kudos
Steve_Lionel
Honored Contributor III
975 Views

Doing this conversion was an interesting learning experience for me, as it often has been when translating MSDN samples over the years. 

0 Kudos
Paul_Curtis
Valued Contributor I
975 Views

Here is a set of ListView wrapper functions.  This is 32-bit code with 4-byte default integers, may have to be modified for 64-bits.

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!
! List view functions
!

!
! Adds a new column to a list view. The columnIndex is both the
! column position in the list view and the index of the associated
! subitem. The title is displayed for the column in the list view
! header, and the width is the column width in pixels.
!
SUBROUTINE ListViewAddColumn (hwnd, controlId, columnIndex, title, width, extraFormat)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: columnIndex
    CHARACTER(LEN=*), INTENT(IN)   :: title
    INTEGER, INTENT(IN)            :: width
	INTEGER, INTENT(IN),OPTIONAL   :: extraFormat

    TYPE(T_LV_COLUMN)              :: column
    INTEGER                        :: rval

    column%iSubItem = columnIndex
    column%pszText  = LOC(title)
    column%cx       = width
    column%mask     = IOR(LVCF_SUBITEM, LVCF_WIDTH)
    
	! extraFormat denotes text_is_centered or item_is_an_image
	IF (PRESENT(extraFormat)) THEN
		column%fmt = extraFormat
		column%mask = IOR(LVCF_FMT, column%mask)
		IF (extraFormat /= LVCFMT_IMAGE) column%mask = IOR(column%mask, LVCF_TEXT)
	
	!	if there is no extra argument, text content is assumed
	ELSE
		column%mask = IOR(column%mask, LVCF_TEXT)
	END IF
			
	rval = SendControlMessage(hwnd, controlId, LVM_INSERTCOLUMN, columnIndex, LOC(column))
    IF(rval == -1) THEN
        CALL ControlError("ListViewAddColumn", controlId, "failed")
    END IF

END SUBROUTINE ListViewAddColumn


!
! Returns the number of items in a list view.
!
INTEGER FUNCTION ListViewGetNumItems(hwnd, controlId)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId

    INTEGER                        :: rval

    rval = SendControlMessage(hwnd, controlId, LVM_GETITEMCOUNT, 0, 0)
    IF(rval >= 0) THEN
        ListViewGetNumItems = rval
    ELSE
        CALL ControlError("ListViewGetNumItems", controlId, &
            "LVM_GETITEMCOUNT")
        ListViewGetNumItems = 0
    END IF

END FUNCTION ListViewGetNumItems


SUBROUTINE ListViewWideHighlight (hwnd, controlId)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId

    INTEGER                        :: rval

    rval = SendControlMessage (hwnd, controlId,					&
							   LVM_SETEXTENDEDLISTVIEWSTYLE,	&
							   LVS_EX_FULLROWSELECT,			&
							   LVS_EX_FULLROWSELECT)
END SUBROUTINE ListViewWideHighlight


!	enable hover-detection for a listview control; hover information
!	is returned via LVN_HOTTRACK messages within WM_NOTIFY, and in this
!	program HandleListViewClick is used to resolve the selected item
SUBROUTINE ListViewHoverEnable (hwnd, controlId)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId

    INTEGER                        :: rval

    rval = SendControlMessage (hwnd, controlId,					&
							   LVM_SETEXTENDEDLISTVIEWSTYLE,	&
							   LVS_EX_TRACKSELECT,				&
							   LVS_EX_TRACKSELECT)
END SUBROUTINE ListViewHoverEnable



!
! Removes all the items in a list view.
!
SUBROUTINE ListViewDeleteAllItems (hwnd, controlId)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId

    INTEGER                        :: rval

    rval = SendControlMessage(hwnd, controlId, LVM_DELETEALLITEMS, 0, 0)
    IF (rval == 0) THEN
        CALL ControlError("ListViewDeleteAllItems", controlId, &
            "LVM_DELETEALLITEMS")
    END IF
    rval = SendControlMessage(hwnd, controlId, LVM_UPDATE, 0, 0)
    IF( rval == 0) THEN
        CALL ControlError("ListViewDeleteAllItems", controlId, &
            "LVM_UPDATE")
    END IF

END SUBROUTINE ListViewDeleteAllItems

!
! Adds an item to a list view. Returns the 1-based item index, 
! or -1 if the operation fails.
!
INTEGER FUNCTION ListViewAddItem (hwnd, controlId, name)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    CHARACTER(LEN=*), INTENT(IN)   :: name

    INTEGER                        :: rval
    INTEGER                        :: nItems
    TYPE(T_LV_ITEM)                :: item
    CHARACTER(LEN=200)             :: buffer
    
    buffer = name
    CALL NullTerminateString (buffer)

    nItems        = ListViewGetNumItems (hwnd, controlId)
    item%mask     = LVIF_TEXT
    item%iItem    = nItems
    item%iSubitem = 0
    item%pszText  = LOC(buffer)
    
    rval = SendControlMessage(hwnd, controlId, LVM_INSERTITEM, 0, LOC(item))
    
    IF(rval /= -1) THEN
        ListViewAddItem = rval + 1
    ELSE
        CALL ControlError("ListViewAddItem", controlId, "LVM_INSERTITEM")
        ListViewAddItem = -1
    END IF

END FUNCTION ListViewAddItem


!
! Sets the text in a column for a single item in a list view control.
!                                             itemindex = row
SUBROUTINE ListViewSetColumn (hwnd, controlId, row, column, text, color)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: row
    INTEGER, INTENT(IN)            :: column
    CHARACTER(LEN=*), INTENT(IN)   :: text
	INTEGER, INTENT(IN), OPTIONAL  :: color

    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item
    CHARACTER(LEN=200)             :: buffer

	IF (PRESENT(color)) then
		rval = SendControlMessage (hwnd, controlId, LVM_SETTEXTCOLOR, 0, color)
	END IF

    buffer = text
    CALL NullTerminateString(buffer)

    item%mask     = LVIF_TEXT
    item%iItem    = row - 1		! row    is 1-based
    item%iSubitem = column		! column is 0-based
    item%pszText  = LOC(buffer)
    rval = SendControlMessage (hwnd, controlId, LVM_SETITEM, 0, LOC(item))
    IF (rval == -1) THEN
        CALL ControlError("ListViewSetColumn", controlId, "LVM_SETITEM")
    END IF

END SUBROUTINE ListViewSetColumn


SUBROUTINE ListViewSetImage (hwnd, controlId, row, column, image)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: row
    INTEGER, INTENT(IN)            :: column
    INTEGER, INTENT(IN)            :: image

    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item

    item%mask     = LVIF_IMAGE
    item%iItem    = row - 1		! row    is 1-based
    item%iSubitem = column		! column is 0-based
    item%iImage   = image
    rval = SendControlMessage (hwnd, controlId, LVM_SETITEM, 0, LOC(item))
    IF (rval == -1) THEN
        CALL ControlError("ListViewSetImage", controlId, "LVM_SETITEM")
    END IF
END SUBROUTINE ListViewSetImage


SUBROUTINE ListViewSetColumnHeader (hwnd, controlId, zb_colpos, text)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: zb_colpos		! zero-based column position
    CHARACTER(LEN=*), INTENT(IN)   :: text

    INTEGER                        :: rval
    TYPE(T_LVCOLUMN)               :: lvcolumn
    CHARACTER(LEN=100)             :: buffer

    buffer = text
    CALL NullTerminateString(buffer)

    lvcolumn%mask		= LVCF_TEXT
    lvcolumn%pszText	= LOC(buffer)
    lvcolumn%cchTextMax	= INDEX(buffer,CHAR(0))
	
	rval = SendControlMessage (hwnd, controlId, LVM_SETCOLUMN, zb_colpos, LOC(lvcolumn))
    IF (rval == -1) THEN
        CALL ControlError("ListViewSetColumnHeader", controlId, "LVM_SETCOLUMN")
    END IF
END SUBROUTINE ListViewSetColumnHeader


! 
! Sets the specified item in a list view control to selected. The
! index argument is 1-based.
!
SUBROUTINE ListViewSetSelectedIndex(hwnd, controlId, index)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: index
    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item
    
    item%iItem     = index - 1
    item%iSubitem  = 0
    item%mask      = LVIF_STATE
    item%state     = LVIS_SELECTED
    item%stateMask = LVIS_SELECTED
	 
    rval = SendControlMessage (hwnd, controlId, LVM_SETITEM, 0, LOC(item))
    IF (rval == -1) THEN
        CALL ControlError("ListViewSetSelectedIndex", controlId, &
            "LVM_SETITEM")
    END IF
END SUBROUTINE ListViewSetSelectedIndex


SUBROUTINE ListViewDeselect (hwnd, controlId)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER				           :: index
    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item
	index = ListViewGetSelectedIndex (hwnd, controlId)
	IF (index /= -1) THEN
		
		item%iItem     = index - 1
		item%iSubitem  = 0
		item%mask      = LVIF_STATE
		item%state     = 0
		item%stateMask = LVIS_SELECTED 
		
		rval = SendControlMessage (hwnd, controlId, LVM_SETITEM, 0, LOC(item))
		IF (rval == -1) THEN
			CALL ControlError("ListViewSetSelectedIndex", controlId, &
				"LVM_SETITEM")
        END IF
	END IF
END SUBROUTINE ListViewDeselect


!
! Returns the 1-based index of the currently selected item in a list view,
! or -1 if nothing is selected.
!
INTEGER FUNCTION ListViewGetSelectedIndex (hwnd, controlId, top) RESULT(index)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
	INTEGER, INTENT(INOUT),OPTIONAL:: top

    INTEGER                        :: rval
    INTEGER                        :: nItems
    TYPE(T_LV_ITEM)                :: lvitem
	TYPE(T_RECT)				   :: rect
    INTEGER                        :: i

    nItems = ListViewGetNumItems (hwnd, controlId)
    DO i = 0, nItems - 1
        lvitem%mask		 = LVIF_STATE
        lvitem%iItem	 = i
        lvitem%iSubitem	 = 0
        lvitem%stateMask = LVIS_SELECTED
        rval = SendControlMessage (hwnd, controlId, LVM_GETITEM, 0, LOC(lvitem))
        IF(rval /= 0) THEN
            IF (lvitem%state == LVIS_SELECTED) THEN
                IF (PRESENT(top)) THEN
					rval = SendControlMessage (hwnd, controlId, LVM_GETITEMRECT, i, LOC(re
					top = rect%top
				END IF
				index = i + 1
                RETURN
            END IF
        ELSE
            CALL ControlError("ListViewGetSelectedItem", controlId, "LVM_GETITEM")
        END IF
    END DO
    index = -1

END FUNCTION ListViewGetSelectedIndex


!
! Associates an integer value with a list view item, which can later
! be retrieved with ListViewGetItemData.
!
!  If the data is being stored for later use with NM_CUSTOMDRAW, such as
!  for setting a custom color for each element in the LV, this associated
!  integer vaue is returned within the NM_CUSTOMDRAW data structure as
!                nmlvcd%nmcd%lItemlParam

SUBROUTINE ListViewSetItemData (hwnd, controlId, index, valu)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: index
    INTEGER, INTENT(IN)            :: valu

    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item
    
    item%iItem    = index - 1
    item%iSubitem = 0
    item%mask     = LVIF_PARAM
    item%lparam   = valu
    rval = SendControlMessage(hwnd, controlId, LVM_SETITEM, 0, LOC(item))
    IF(rval == -1) THEN
        CALL ControlError("ListViewSetItemData", controlId, "LVM_SETITEM")
    END IF

END SUBROUTINE ListViewSetItemData


!
! Retrieves an integer data value associated with a list view item.
! If the operation fails, -1 is returned.
!
INTEGER FUNCTION ListViewGetItemData(hwnd, controlId, index) RESULT(valu)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: index

    INTEGER                        :: rval
    TYPE(T_LV_ITEM)                :: item
     
    item%iItem    = index - 1
    item%iSubitem = 0
    item%mask     = LVIF_PARAM
    rval = SendControlMessage(hwnd, controlId, LVM_GETITEM, 0, LOC(item))
    IF(rval /= -1) THEN
        valu = item%lparam
    ELSE
        CALL ControlError("ListViewGetItemData", controlId, "LVM_GETITEM")
        valu = -1
    END IF

END FUNCTION ListViewGetItemData


!
! Retrieves the integer data value associated with the currently
! selected item in the list view, or -1 if no item is currently
! selected.
!
INTEGER FUNCTION ListViewGetSelectedData(hwnd, controlId) RESULT(valu)

    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId

    INTEGER                        :: sel

    sel = ListViewGetSelectedIndex(hwnd, controlId)
    IF(sel /= -1) THEN
        valu = ListViewGetItemData(hwnd, controlId, sel)
    ELSE
        valu = -1
    END IF

END FUNCTION ListViewGetSelectedData


! Call this function in response to the NM_CLICK message.  It
! causes a row to be selected if it is clicked on anywhere, not
! just in the first column.
!
SUBROUTINE HandleListViewClick (hwnd, controlId, got_one)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
	LOGICAL, INTENT(OUT),OPTIONAL  :: got_one

    INTEGER                        :: rval
    INTEGER                        :: nItems
    INTEGER(HANDLE)                :: hwndControl
    INTEGER                        :: i
    TYPE(T_RECT)                   :: rect
    TYPE(T_POINT)                  :: position
    TYPE(T_LV_ITEM)                :: item
	
	IF (PRESENT(got_one)) got_one = .FALSE.
	IF (n_enterwindows /= 0) RETURN

	! Probably should be GetMessagePos, but that's broken in DVF's
    ! headers, and this fills the bill OK.
    rval        = GetCursorPos (position)
    hwndControl = DialogGetControlWindow (hwnd, controlId)
    rval        = ScreenToClient (hwndControl, position)

    nItems = SendControlMessage (hwnd, controlId, LVM_GETITEMCOUNT, 0, 0)
    DO i = 0, nItems - 1
        rect%left = LVIR_BOUNDS 
        rval = SendControlMessage(hwnd, controlId, LVM_GETITEMRECT, i, LOC(rect))
        IF (PtInRect(rect, position)) THEN
            item%mask		= LVIF_STATE
            item%state		= IOR(LVIS_SELECTED, LVIS_FOCUSED)
            item%stateMask	= IOR(LVIS_SELECTED, LVIS_FOCUSED)
            rval = SendControlMessage (hwnd, controlId, LVM_SETITEMSTATE, i, LOC(item))
			IF (PRESENT(got_one)) got_one = .TRUE.
			EXIT
        END IF
    END DO

END SUBROUTINE HandleListViewClick


!	resolve a listview NM_HOVER message into the 1-based
!	index of the listview item which is being hovered over;
SUBROUTINE ListViewHover (hwnd, controlId, item)
    IMPLICIT NONE

    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(OUT)           :: item

    INTEGER                        :: rval, i
    INTEGER                        :: nItems
    INTEGER(HANDLE)                :: hwndControl
    TYPE(T_RECT)                   :: rect
    TYPE(T_POINT)                  :: position

	! Probably should be GetMessagePos, but that's broken in DVF's
    ! headers, and this fills the bill OK.
    rval        = GetCursorPos (position)
    hwndControl = DialogGetControlWindow (hwnd, controlId)
    rval        = ScreenToClient (hwndControl, position)

    nItems = SendControlMessage (hwnd, controlId, LVM_GETITEMCOUNT, 0, 0)
    DO i = 0, nItems - 1
        rect%left = LVIR_BOUNDS 
        rval = SendControlMessage(hwnd, controlId, LVM_GETITEMRECT, i, LOC(rect))
        IF (PtInRect(rect, position)) THEN
			item = i + 1
			RETURN
		END IF
    END DO
	item = 0

END SUBROUTINE ListViewHover

 

0 Kudos
Reply