Software Archive
Read-only legacy content
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.
17060 Discussions

Missing Win32 controls - DateTimePicker, MonthCal

pcurtis
Beginner
586 Views
The DateTimePicker and MonthCal control types are still not supported by CVF6.6, at least via the easy way of setting up dialogs using the Resource Editor within DevStudio. I would very much appreciate any hints or code samples on how to implement these controls in a dialog, the "hard" way.

TIA, Paul Curtis
pcurtis@kiltel.com
0 Kudos
2 Replies
Jugoslav_Dujic
Valued Contributor II
586 Views
Well, here's a snippet from an actual app containing a dialog with two DateTimePickers IDC_SPIN_YEAR and IDC_SPIN_HOUR (one for date, one for time). I apologize for overhead, since it evolved from an older code which utilized edits and spins instead. When MODE.NE.MODE_ONLINE, they behave as pickers; otherwise, they are disabled and act like a clock, driven by timer. Helper functions are not necessary (they used to be far bigger); they update global iHgod, iHdan etc. dTime is double in format YYYYMMDD.hhmmss used for interchange between helpers.

 
!=============================================================== 
LOGICAL(4) FUNCTION TimeDlgProc(hWnd,Msg,wParam,lParam) 
!DEC$ATTRIBUTES STDCALL:: TimeDlgProc 
 
USE Whatever_needed 
 
IMPLICIT NONE 
 
INCLUDE "Resource.fd" 
 
INTEGER::                     hWnd,Msg,wParam,lParam 
 
TYPE(T_SYSTEMTIME)::          TST 
TYPE(T_NMHDR)::               Header; POINTER(lpHeader,Header) 
CHARACTER(40)::               sTimeFormat 
CHARACTER(20)::               sDateFormat 
REAL(8)::                     dTime,dCurrTime 
 
SELECT CASE(Msg) 
CASE (WM_INITDIALOG) 
      iSt=GetLocaleInfo(LOCALE_USER_DEFAULT, LOCALE_STIMEFORMAT, sTimeFormat, LEN(sTimeFormat)) 
      iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_HOUR),DTM_SETFORMAT,0,LOC(sTimeFormat)) 
 
      iSt=GetLocaleInfo(LOCALE_USER_DEFAULT, LOCALE_SSHORTDATE, sDateFormat, LEN(sDateFormat)) 
      iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_YEAR),DTM_SETFORMAT,0,LOC(sDateFormat)) 
 
      CALL GetLocalTime(TST) 
      CALL InitTimeControls(hWnd,TST%wMinute,TST%wHour,TST%wDay,TST%wMonth,TST%wYear) 
      iSt=GetDlgTime(hWnd,dTime) 
      CALL UpdateTime(dTime) 
      TimeDlgProc=.FALSE. 
CASE (WM_NOTIFY) 
      lpHeader=lParam 
      IF (wParam.EQ.IDC_SPIN_HOUR .OR. wParam.EQ.IDC_SPIN_YEAR) THEN 
            IF (Header%Code.EQ.DTN_DATETIMECHANGE) THEN 
                  iSt=GetDlgTime(hWnd,dTime) 
                  CALL UpdateTime(dTime) 
            END IF 
      ELSE 
            TimeDlgProc=.FALSE. 
      END IF 
CASE (WM_TIMER) 
      CALL GetLocalTime(TST) 
      IF (MODE.EQ.MODE_ONLINE) THEN 
            iSt=SendMessage(GetDlgItem(hWnd, IDC_SPIN_HOUR), DTM_SETSYSTEMTIME, GDT_VALID, LOC(TST)) 
            iSt=SendMessage(GetDlgItem(hWnd, IDC_SPIN_YEAR), DTM_SETSYSTEMTIME, GDT_VALID, LOC(TST)) 
            iSt=GetDlgTime(hWnd,dTime) 
            CALL UpdateTime(dTime) 
      TimeDlgProc=.FALSE. 
CASE DEFAULT 
      TimeDlgProc=.FALSE. 
END SELECT 
 
END FUNCTION TimeDlgProc 


continued...
0 Kudos
Jugoslav_Dujic
Valued Contributor II
586 Views
...continued:
 
!============================================================== 
SUBROUTINE InitTimeControls(hWnd,iMinute,iHour,iDay,iMonth,iYear) 
!Sets values of DateTimePickers 
 
USE DFWIN 
USE COMCTL 
USE DTPICKER 
 
IMPLICIT NONE 
 
INCLUDE "Resource.fd" 
 
INTEGER,INTENT(IN)::    hWnd 
INTEGER(2),INTENT(IN):: iMinute,iHour,iDay,iMonth,iYear 
 
TYPE(T_SYSTEMTIME)::    TST 
INTEGER::               iSt 
 
CALL GetLocalTime(TST) 
 
TST=T_SYSTEMTIME(INT2(iYear),INT2(iMonth),5,INT2(iDay),INT2(iHour),INT2(iMinute),0_2,0_2) 
 
iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_HOUR), DTM_SETSYSTEMTIME, GDT_VALID, LOC(TST)) 
iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_YEAR), DTM_SETSYSTEMTIME, GDT_VALID, LOC(TST)) 
 
END SUBROUTINE InitTimeControls 
!=============================================================== 
LOGICAL(4) FUNCTION GetDlgTime(hWnd,dTime) 
!Retrieves values of DateTimePickers into dTime 
 
USE DFWIN 
USE COMCTL 
USE DTPICKER 
USE STRINGS 
 
IMPLICIT NONE 
 
INCLUDE "Resource.fd" 
 
INTEGER,INTENT(IN)::    hWnd 
REAL(8),INTENT(OUT)::   dTime 
 
TYPE(T_SYSTEMTIME)::    tTime, tDate 
INTEGER::               iSt 
 
GetDlgTime=.TRUE. 
 
iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_HOUR), DTM_GETSYSTEMTIME, 0, LOC(tTime)) 
iSt=SendMessage(GetDlgItem(hWnd,IDC_SPIN_YEAR), DTM_GETSYSTEMTIME, 0, LOC(tDate)) 
 
dTime=10000._8*tDate%wYear + 100._8*tDate%wMonth + tDate%wDay + & 
      tTime%wHour/100._8 + tTime%wMinute/10000._8 
 
END FUNCTION GetDlgTime 
!================================================================ 
SUBROUTINE UpdateTime(dTime) 
!Copies contents of dTime into global iH* variables 
 
USE HISTORY 
USE me_com1 
 
IMPLICIT NONE 
 
REAL(8),INTENT(IN)::    dTime 
 
REAL(8)::               dTime2 
 
iHGod=INT(dTime)/10000 
iHMes=(INT(dTime)-10000*iHGod)/100 
iHDan=INT(dTime)-10000*iHGod-100*iHMes 
dTime2=dTime-INT(dTime) 
iHSat=INT(100*dTime2) 
iHMin=NINT(10000*dTime2)-100*iHsat 
iVrem=NINT(10000*dTime2) 
iDatMer=INT(dTime) 
 
END SUBROUTINE UpdateTime 

Dialog, if modal, is invoked using
hTimeDlg=DialogBox(hInst,MAKEINTRESOURCE(IDD_DIALOG_TIME),hFrame,    & 
      LOC(TimeDlgProc))

Also, you have to initialize datetime classes somewhere at application start:
 
TYPE (T_INITCOMMONCONTROLSEX)::  iCCE 
iCCE%dwSize=8 
iCCE%dwICC=ICC_DATE_CLASSES 
iSt=InitCommonControlsEx(iCCE) 

HTH

Jugoslav
0 Kudos
Reply