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

LISTVIEW CONTROL

longwell
Beginner
497 Views
I am familiar with the Listbox and have used it successfully many times. Now, I am attempting to use the LISTVIEW control in a dialog box. I have successfully loaded data into the control, but now I want the application to call a subroutine when an a row is clicked in the LISTVIEW control. I have used the "dlgsetsub" funtion to define which callback subroutine to call, but nothing happens when a row in the LISTVIEW control is clicked. Should this work or should I be doing something different. Any help that you can provide would be greatly appreciated.
0 Kudos
5 Replies
Jugoslav_Dujic
Valued Contributor II
497 Views
Unfortunately, no, ListView is not supported by DFLOGM, so you'll have to cope with pure API handling. This is somewhat less elegant (but more powerful) than Dlg* family of routines.

Here's a code snippet from an actual application which handles the dialog whose screenshot is in the attachment.
(There are two similar ListViews, which are shown/hidden depending on tab control state; I snipped the code which handles the second because it's more or less identical).
It is a bit more complicated since it's from an actual app, but hope it would be helpful.

!=========================================================
INTEGER(4) FUNCTION ScadaIDDlgProc(hWnd,Msg,wParam,lParam)
!DEC$ATTRIBUTES STDCALL::  ScadaIDDlgProc
USE DFWIN
USE LANGDEP
USE OPCCLIENT
USE COMCTL
USE STRINGS
USE REGISTRY
USE UKS
USE me_com1

IMPLICIT NONE

INCLUDE "Resource.fd"

INTEGER, INTENT(IN)::  hWnd, Msg, wParam, lParam

INTEGER::               i, iSt, hIcon, iIcon
INTEGER, SAVE::         hImageList = 0, hList1, hList2
CHARACTER(100)::        sID
TYPE(T_LV_ITEM)::       Item
TYPE(T_TC_ITEM)::       TabItem
TYPE(T_LV_COLUMN)::     Column
TYPE(T_NM_LISTVIEW)::   LV; POINTER(pLV,LV)
TYPE(T_NMHDR)::         Hdr; POINTER(pHdr,Hdr)
INTEGER, PARAMETER::    sColumn(0:4)=(/S_SCADAID, S_DMSID, S_STATUS, S_QUALITY, S_LOCATION/)
INTEGER, PARAMETER::    sMerColumn(0:5)=(/S_SCADAID, S_DMSID, S_VALUE, S_TYPE, &
S_QUALITY, S_LOCATION/)
INTEGER, PARAMETER::    sQuality(1:3)=(/S_GOOD, S_UNCERTAIN, S_BAD/)
INTEGER, PARAMETER::    iColWidth(0:4)=(/60, 60, 40, 40, 312/)
INTEGER, PARAMETER::    iMerColWidth(0:5)=(/60, 60, 60, 40, 40, 252/)
INTEGER, PARAMETER::    idIcon(0:2)=(/IDI_ICON_GOOD, IDI_ICON_UNCERTAIN, IDI_ICON_BAD/)
!This is the function for sorting elements by columns
INTERFACE
      INTEGER FUNCTION ListSortFunc(i1,i2,i3)
      !DEC$ATTRIBUTES STDCALL::  ListSortFunc
      INTEGER:: i1,i2,i3
      END FUNCTION ListSortFunc
END INTERFACE


SELECT CASE(MSG)
CASE (WM_INITDIALOG)
      hList1 = GetDlgItem(hWnd, IDC_LIST1)
      hList2 = GetDlgItem(hWnd, IDC_LIST2)

      TabItem%mask = TCIF_TEXT
      TabItem%pszText = LOC(sID)
      !.C. is a character function which loads a string 
      !from a dll string table. Use normal strings instead.
      sID = .C.S_SWITCHGEAR
      iSt = SendMessage(GetDlgItem(hWnd, IDC_TAB1), TCM_INSERTITEM, 0, LOC(TabItem))
      sID = .C.S_MEASUREMENTS
      iSt = SendMessage(GetDlgItem(hWnd, IDC_TAB1), TCM_INSERTITEM, 1, LOC(TabItem))

      iSt = ShowWindow(hList1, SW_SHOW)
      iSt = ShowWindow(hList2, SW_HIDE)
      iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC1), SW_SHOW)
      iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC2), SW_HIDE)
      iSt = SendMessage(GetDlgItem(hWnd, IDOK), BM_SETIMAGE, IMAGE_ICON, hicoOK)
      !Setting up the header control
      DO i=0,4
            Column%mask = LVCF_FMT + LVCF_ORDER + LVCF_SUBITEM + LVCF_TEXT + LVCF_WIDTH
            Column%fmt = LVCFMT_LEFT 
            Column%cx = iColWidth(i)
            sID = .C.sColumn(i)
            Column%pszText = LOC(sID) 
            Column%cchTextMax = 0 
            Column%iSubItem = i
            Column%iImage = 0
            Column%iOrder = i
            iSt = SendMessage(hList1, LVM_INSERTCOLUMN, i, LOC(Column))
      END DO
      DO i=0,5
            sID = .C.sMerColumn(i)
            Column%cx = iMerColWidth(i)
            Column%iSubItem = i
            Column%iOrder = i
            iSt = SendMessage(hList2, LVM_INSERTCOLUMN, 
i, LOC(Column))
      END DO

      DO i=1,iBrKom
            IF (iRConPr(i).NE.0) THEN
                  iIcon = 0

                  Item%mask = LVIF_TEXT + LVIF_IMAGE + LVIF_PARAM
                  Item%iItem = 0
                  Item%state = 0
                  Item%statemask = 0
                  Item%cchTextMax = 0
                  Item%iImage = -1
                  !lParam is optional; here it is used 
                  !to associate data with each row, in 
                  !order to enable sorting
                  Item%lParam = i

                  Item%iSubItem = 0
                  CALL GetScadaID(i, 1, sID)
                  IF (LEN_TRIM(sID).LE.1) iIcon = 1
                  sID = TRIM(sID)//CHAR(0)
                  Item%pszText = LOC(sID)
                  iSt = SendMessage(hList1, LVM_INSERTITEM, 0, LOC(Item))

                  Item%mask = LVIF_TEXT
                  Item%iSubItem = 1
                  sID = STRING(iSifPr(i),9)
                  sID = TRIM(sID)//CHAR(0)
                  iSt = SendMessage(hList1, LVM_SETITEM, 0, LOC(Item))

                  Item%iSubItem = 2
                  sID = STRING(iStPr(i),1)
                  sID = TRIM(sID)//CHAR(0)
                  iSt = SendMessage(hList1, LVM_SETITEM, 0, LOC(Item))

                  Item%iSubItem = 3
                  sID = .C.sQuality(iRConPr(i))
                  Item%iImage = iRConPr(i)-1
                  iSt = SendMessage(hList1, LVM_SETITEM, 0, LOC(Item))

                  Item%iSubItem = 4
                  CALL GetSwitchName(iSifPr(i), sID, .TRUE., iSt)
                  IF (LEN_TRIM(sID).LE.1) iIcon = 2
                  sID = TRIM(sID)//CHAR(0)
                  iSt = SendMessage(hList1, LVM_SETITEM, 0, LOC(Item))

                  IF (iIcon.NE.0) THEN
                        Item%mask = LVIF_IMAGE
                        Item%iSubItem = 0
                        Item%iImage = iIcon
                        iSt = SendMessage(hList1, LVM_SETITEM, 0, LOC(Item))
                  END IF
            END IF
      END DO
!

!Adding icons to the list
      hImageList = ImageList_Create(16, 16, ILC_COLOR+ILC_MASK, 6, 2)
      DO i=0,2
            hIcon = LoadImageA(hInst, idIcon(i), IMAGE_ICON, 16, 16, LR_DEFAULTCOLOR )
            iSt = ImageList_ReplaceIcon(hImageList, -1, hIcon)
      END DO
      iSt = SendMessage(hList1, LVM_SETIMAGELIST, LVSIL_SMALL, hImageList)
      iSt = SendMessage(hList2, LVM_SETIMAGELIST, LVSIL_SMALL, hImageList)

      ScadaIDDlgProc = .FALSE.
CASE (WM_COMMAND)
      IF (LOWORD(wParam).EQ.IDOK) THEN
            iSt = EndDialog(hWnd, IDOK)
      END IF
      ScadaIDDlgProc = .TRUE.
CASE (WM_NOTIFY)
      pHdr = lParam
      IF (wParam.EQ.IDC_LIST1) THEN
            IF (hdr%code.EQ.LVN_COLUMNCLICK) THEN
                  pLV = lParam
                  iSt = SendMessage(hList1, LVM_SORTITEMS, LV%iSubItem+1, LOC(ListSortFunc))
            END IF
      ELSE IF (wParam.EQ.IDC_LIST2) THEN
            IF (hdr%code.EQ.LVN_COLUMNCLICK) THEN
                  pLV = lParam
                  iSt = SendMessage(hList2, LVM_SORTITEMS, -LV%iSubItem-1, LOC(ListSortFunc))
            END IF
      ELSE IF (wParam.EQ.IDC_TAB1) THEN
            IF (hdr%code.EQ.TCN_SELCHANGE) THEN
                  iSt = SendMessage(GetDlgItem(hWnd, IDC_TAB1), TCM_GETCURSEL, 0, 0)
                  IF (iSt.EQ.0) THEN
                        iSt = ShowWindow(hList1, SW_SHOW)
                        iSt = ShowWi
ndow(hList2, SW_HIDE)
                        iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC1), SW_SHOW)
                        iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC2), SW_HIDE)
                  ELSE
                        iSt = ShowWindow(hList1, SW_HIDE)
                        iSt = ShowWindow(hList2, SW_SHOW)
                        iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC1), SW_HIDE)
                        iSt = ShowWindow(GetDlgItem(hWnd,IDC_STATIC2), SW_SHOW)
                  END IF
            END IF
      END IF
CASE DEFAULT
      ScadaIDDlgProc = .FALSE.
END SELECT


END FUNCTION ScadaIDDlgProc
!================================
INTEGER FUNCTION ListSortFunc(i1,i2,iColumn)
!DEC$ATTRIBUTES STDCALL::  ListSortFunc
USE me_com1
USE UKS

IMPLICIT NONE

INTEGER, INTENT(IN)::   i1,i2,iColumn

CHARACTER(100)::        sID1, sID2
INTEGER::               iSt

IF (iColumn.GT.0) THEN
      !Prekidaci
      SELECT CASE (iColumn)
      CASE(1)
            CALL GetScadaID(i1, 1, sID1)
            CALL GetScadaID(i2, 1, sID2)
            IF (sID1.EQ.sID2) THEN
                  ListSortFunc = 0
            ELSE IF (sID1.GT.sID2) THEN
                  ListSortFunc = 1
            ELSE
                  ListSortFunc = -1
            END IF
      CASE(2)
            ListSortFunc = iSifPr(i1)-iSifPr(i2)
!Snipped the rest


HTH
Jugoslav
0 Kudos
longwell
Beginner
497 Views
Thanks for the input. I was hoping there may be an easy way to use a LISTVIEW control without getting to deep into API handling. Any thoughts on how to handle a LISTVIEW while still using DFLOGM would be appreciated.

Joe
0 Kudos
Jugoslav_Dujic
Valued Contributor II
497 Views
Well, there are two ways, none of them particularly attractive:

- The "pure" way is to use ActiveX wrapper for ListView control (it is located in comctl32.ocx). All that ActiveX stuff is Greek to me so you'll have to rely on samples, MSDN documentation and pelhaps help from other Forum participants.

- The other way is to tweak DFLOGM.f90 (my favourite sport) to roll your own ListView (or, perhaps, general "unknown control") support, i.e. develop the structure, handle WM_COMMAND and WM_NOTIFY etc.

Jugoslav
0 Kudos
onkelhotte
New Contributor II
497 Views
Hi there,
I created a ListView Control and I am able toinsert new columns, items etc. The difference is the implemantation of the code. You insert new data by messages, I set them when I create the dialog within the MainDialog Callback Routine.
Now I tried to implement two features: Sorting the columns and edit the label. But where do I "intercept" the WM_NOTIFY Message? Do I have to rewrite the code?
Code:
l = DlgInit(IDD_DIALOG_Main, dlgMain)
l = DlgSetSub(dlgMain, IDD_DIALOG_Main, MainInit)
...
l = DlgModeless(dlgMain)
do while( GetMessage (mesg, NULL, 0, 0) )
  if (DlgIsDlgMessage(mesg) .EQV. .FALSE. ) then
    lret = TranslateMessage( mesg )
    ret  = DispatchMessage( mesg )
  end if
end do
...

! *********************************************************************
SUBROUTINE MainInit( dlg, id, callbacktype )
! *********************************************************************
use...
ListHwnd = GetDlgItem(dlg.hwnd,IDC_LIST_Chemie)
l = SendMessage(ListHwnd,LVM_SETEXTENDEDLISTVIEWSTYLE,0,LVS_EX_FULLROWSELECT)

LVColumn.mask = LVCF_FMT+LVCF_ORDER+LVCF_SUBITEM+LVCF_TEXT+LVCF_WIDTH
LVColumn.cchTextMax = 0 
LVColumn.iImage = 0

LVColumn.fmt = LVCFMT_RIGHT
...
l = SendMessage(ListHwnd, LVM_INSERTCOLUMN, 0, LOC(LVColumn))

LVColumn.fmt=LVCFMT_LEFT
...
l = SendMessage(ListHwnd, LVM_INSERTCOLUMN, 1, LOC(LVColumn))
...
end subroutin
0 Kudos
Jugoslav_Dujic
Valued Contributor II
497 Views
Basically, you can't :-(. Either you must tweak DFLOGM.f90 code or insert an ugly


if (Msg%message.EQ.WM_NOTIFY .AND. Msg%hWnd.EQ.Dlg%hWnd .AND. &
(the NMHDR%idFrom is listview control)) then
!do something
else
TranslateMessage
DispatchMessage
end if


In the meantime, I developed ListView support in <XFT library with kind help of Mike Gaitens -- check out the LVTest sample.

I hope the code and documentation are clear enough.

Jugoslav
0 Kudos
Reply