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

fortran's death, motorcyles and dialog boxes.

John_N_2
Beginner
755 Views
Dear Steve:

Is Fortran dead? Whenever I mention that I use it and like it - I may as well be in a Charles Dickens novel. When I mention that Intel makes a damn fine compiler then I am just wasting my breath. I am not really seeking comments, more saying that sometimes without this site a human feels very alone. I tend to identify stongly with the Neandertahls in the National Geographic, and went into a state of ernest rage when they asked if the recreated NM should live in a zoo.

I could see the pictures - here is the Neanderthal Man and beside him is the Fortran Man - see the punch cards.

I hate motorcycles although the Zen book was ok,

Now the real question, I have some legacy code that dates from the period 1988 to 1993. It was first started on a Compaq Portable, green screen, no HD and 8086 chip. I hated every Microsoft Fortran Complier after 3.3, PowerStation was a dog on my firehydrant code and the CVF compiler was interesting. However, I like my Intel compiler, even though it has taken me several years to getg it working so I can use it with MS Studio 2008. Not the compliers fault I was just busy.

I am porting an old Sewer Design Program from DOC based screen calls to Windows. I am having a lot of trouble with the simple dialog box. I have a lot of manuals that explain a lot of the examples, including the TEMPERATURE one, which I found in a Microsoft Fortran Powerstation Manual, which is the best manual for explaining the functions.

I want to have simple data dialogs that allow me to enter integers and reals (I understand the character to real conversion using a read) in groups of 2 numbers to about 10 numbers.

I can set up the RC file, I understand the basics of the calls, but the timing of the events is really hard to follow, so my write statements either miss the data or give it to me multiple times. I tried adding files, but it just crashed on me.

So here is the code, Datum works, Plostd gives me zeros or ***********. Uisng commons was the only way I could figure out how to get my values back.

I have downloaded and played with a lot of dialog boxes, I have read the Lawrence Book, they helped with the single element dialog boxes called from WINMAIN, but these boxes are proving tricky.

A simple code for a 10 element dialog box which reads the elements into reals and ints would be agreat help if one exists?

JMN

!****************************************************************************
!
! SUBROUTINE: Datum
!
! PURPOSE: Displays the Datum Box
!
!****************************************************************************

SUBROUTINE DATUM(L)

use user32

USE IFLOGM
IMPLICIT NONE
INCLUDE 'RESOURCE.FD'


INTEGER retint,L,iret
LOGICAL retlog
character*8 text
real aht, far
TYPE (dialog) dlg

common /GROW1/ aht




EXTERNAL UpdateTemp


! Initialize.

IF ( .not. DlgInit( idd_temp, dlg ) ) THEN
text ="String"
iret = MessageBox(NULL, Text,"Error: dialog not found"C, MB_OK )

ELSE

! Set up Datum controls.
If (L .eq. 1) then
Text = '1'
ELSEIF (L .eq. 2) then
Text = '2'
ELSEIF (L .eq. 3) then
Text = '3'
ELSEIF (L .eq. 4) then
Text = '4'
ELSEIF (L .eq. 5) then
Text = '5'
ELSEIF (L .eq. 6) then
Text = '6'
ELSEIF (L .eq. 7) then
Text = '7'
endif

retlog = DlgSet( dlg, IDC_EDIT_CELSIUS, text)
CALL UpdateTemp( dlg, IDC_EDIT_CELSIUS, DLG_CHANGE)
retlog = DlgSetSub( dlg, IDC_EDIT_CELSIUS, UpdateTemp )
retlog = DlgSetSub( dlg, IDC_EDIT_FAHRENHEIT, UpdateTemp )


! Activate the modal dialog.
retint = DlgModal( dlg )
! Release dialog resources.
CALL DlgUninit( dlg )
END IF

WRITE(4,200)AHT
WRITE(3,200)AHT
200 FORMAT('AT Datum:', F10.3)


END SUBROUTINE Datum

!****************************************************************************
!
! SUBROUTINE: UpdateTemp
!
! PURPOSE: Synchronizes the values of the dialog controls
!
!****************************************************************************

SUBROUTINE UpdateTemp( dlg, control_name, callbacktype )
!DEC$ ATTRIBUTES DEFAULT :: UpdateTemp
USE DFLOGM
IMPLICIT NONE
TYPE (dialog) dlg
INTEGER control_name
INTEGER callbacktype
INCLUDE 'RESOURCE.FD'
CHARACTER(256) text
INTEGER cel, far, retint
Real far1, aht
LOGICAL retlog
! Suppress compiler warnings for unreferenced arguments.
INTEGER local_callbacktype

common /GROW1/ aht


local_callbacktype = callbacktype

SELECT CASE (control_name)
CASE (IDC_EDIT_CELSIUS)
! Celsius value was modified by the user so
! update both Fahrenheit and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT_CELSIUS, text )
READ (text, *, iostat=retint) cel



CASE (IDC_EDIT_FAHRENHEIT)
! Fahrenheit value was modified by the user so
! update both celsius and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT_FAHRENHEIT, text )
READ (text, *, iostat=retint) far1

aht=far1

END SELECT



END SUBROUTINE UpdateTemp

!****************************************************************************
!
! SUBROUTINE: UpdateTemp1
!
! PURPOSE: Synchronizes the values of the dialog controls for Plot_STD
!
!****************************************************************************

SUBROUTINE UpdateTemp1( dlg, control_name, callbacktype )
!DEC$ ATTRIBUTES DEFAULT :: UpdateTemp
USE DFLOGM
IMPLICIT NONE
TYPE (dialog) dlg
INTEGER control_name
INTEGER callbacktype
INCLUDE 'RESOURCE.FD'
CHARACTER(256) text
REAL T2,T3, T4, T22,T32,T43
Integer retint
Real far1
LOGICAL retlog
! Suppress compiler warnings for unreferenced arguments.
INTEGER local_callbacktype

common /grow2/ T2,T3,T4

local_callbacktype = callbacktype

SELECT CASE (control_name)
CASE (IDC_EDIT6)
! Celsius value was modified by the user so
! update both Fahrenheit and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT6, text )
READ (text, *, iostat=retint) T22
retlog = DlgGet( dlg, IDC_EDIT7, text )
READ (text, *, iostat=retint)T32
retlog = DlgGet( dlg, IDC_EDIT8, text )
READ (text, *, iostat=retint)T43


END SELECT
T2=T22
T3=T32
T4=T43
END SUBROUTINE UpdateTemp1

! ****************************************************************
!
SUBROUTINE PLOSTD
!
! ****************************************************************

use user32

USE IFLOGM
IMPLICIT NONE
INCLUDE 'RESOURCE.FD'

INTEGER retint,L,iret
LOGICAL retlog
character*8 text, text2, text3
real T2,T3,T4

TYPE (dialog) dlg

common /grow2/ T2,T3,T4

EXTERNAL UpdateTemp1
OPEN(7,FILE='PLOT.STD',STATUS='UNKNOWN')
! Initialize.
IF ( .not. DlgInit( idd_dialog1, dlg ) ) THEN
text ="String"
iret = MessageBox(NULL, Text,"Error: dialog not found"C, MB_OK )

ELSE

! Set up Datum controls.

text = '200'
text2 = '1000.0'
text3 = '2.5'
retlog = DlgSet( dlg, IDC_EDIT6, text)
retlog = DlgSetSub( dlg, IDC_EDIT7, UPDATETEMP1)
retlog = DlgSetSub( dlg, IDC_EDIT8, UPDATETEMP1 )
CALL UpdateTemp1( dlg, IDC_EDIT6, DLG_CHANGE)

! Activate the modal dialog.
retint = DlgModal( dlg )
! Release dialog resources.
CALL DlgUninit( dlg )
END IF


WRITE(7,200)T2,T3,T4
200 FORMAT( F5.0,/,F5.0,/,F3.1)

CLOSE(7,STATUS='KEEP')


RETURN
END


0 Kudos
1 Solution
Paul_Curtis
Valued Contributor I
750 Views

1. Fortran is far from dead, and can easily be used for Win32 programs featuring any GUI feature, but to do this you need to learn the Win32 message-pump architecture (for which you study Petzold, not Lawrence), and write complete Win32 code in which you explicitly handle your own message loops (ie, forget Quickwin). And, by the way, 1988-93 is not even remotely ancient and you are not the only one who lugged a Compaq Plus around the globe.

2. COMMON is obsolete. Put your proc function (ie the message-loop handler called by Windows when your dialog is interacted with) in a module wherein all your required variables are module-local and thus available to your proc, which of course has only the canonical four Win32 integer arguments.

3. Your dialog proc begins (ie, WM_INITDIALOG) by loading the current values of the variables into the Editbox controls, and ends (WM_COMMAND ... ID_OK) by reading the (possibly modified) values back from those edit boxes. Here are a few editbox-related wrapper functions to get you started; in these functions hwnd is the window handle of your dialog, and controlId is the id associated with the editbox control being modified.

[cpp]!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!
! Edit box functions
!

SUBROUTINE EditBoxReadText (hwnd, controlId, text, textLen)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    INTEGER, INTENT(IN)            :: textLen
    CHARACTER(LEN=textLen), INTENT(OUT) :: text
    INTEGER                        :: rval

    text = ""
    rval = SendControlMessage (hwnd, controlId, WM_GETTEXT, &
                               textLen, LOC(text))

	!	return value is number of characters copied
    IF (rval < 0) THEN
        CALL ControlError ("EditBoxReadText", controlId, "WM_GETTEXT")
    END IF

END SUBROUTINE EditBoxReadText


FUNCTION EditBoxGetText (hwnd, controlId, length) RESULT (text)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: length
    CHARACTER(LEN=length)          :: text
    CHARACTER(LEN=length)	       :: contents
    INTEGER                        :: rval, nc

    rval = SendControlMessage (hwnd, controlId, WM_GETTEXT, &
				               length, LOC(contents))

    IF (rval /= 0) THEN
        text = TRIM(contents)

		! remove garbage bytes from remainder of string
		nc = INDEX(text, CHAR(0))
		IF (nc > 0 .AND. nc < length) text(nc:) = CHAR(0)
    ELSE
        CALL ControlError ("EditBoxGetText", controlId, "WM_GETTEXT")
        text = ""
    END IF

END FUNCTION EditBoxGetText


SUBROUTINE EditBoxGetInteger (hwnd, controlId, argval, nulldefault) 
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
	INTEGER, INTENT(INOUT)		   :: argval
	INTEGER, INTENT(IN), OPTIONAL  :: nulldefault

    INTEGER, PARAMETER             :: len = 40
    CHARACTER(LEN=len)             :: contents
    INTEGER                        :: valu
    INTEGER                        :: status, pos

    CALL EditBoxReadText (hwnd, controlId, contents, len)

	!	stop now if no data to convert
	pos = INDEX(contents, CHAR(0))
	IF (is_empty(contents, pos)) THEN
		IF (PRESENT(nulldefault)) argval = nulldefault
		RETURN
    END IF
    CALL CStringToFortran (contents)
    READ (contents, '(I)', IOSTAT=status) valu

	!	only return a new value if the inputstring was successfully read
    IF (status == 0) argval = valu
    
END SUBROUTINE EditBoxGetInteger


!
! Returns the contents of an edit box, interpreted as a 
! hexadecimal integer.
!
!INTEGER FUNCTION EditBoxGetHex (hwnd, controlId) 
!    IMPLICIT NONE 
!    INTEGER(HANDLE), INTENT(IN)    :: hwnd
!    INTEGER, INTENT(IN)            :: controlId
!    INTEGER, PARAMETER             :: len = 40
!    CHARACTER(LEN=len)             :: contents
!    INTEGER                        :: value
!    INTEGER                        :: status
!
!    CALL EditBoxReadText (hwnd, controlId, contents, len)
!    CALL CStringToFortran (contents)
!    READ (contents, '(Z)', IOSTAT=status) value
!    IF (status == 0) THEN
!        EditBoxGetHex = value
!    ELSE
!        EditBoxGetHex = 0
!    END IF
!
!END FUNCTION EditBoxGetHex


SUBROUTINE EditBoxGetReal (hwnd, controlID, argval, nulldefault)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL,INTENT(IN),OPTIONAL	   :: nulldefault
	REAL,INTENT(INOUT)			   :: argval

    INTEGER, PARAMETER             :: maxchars = 40
    CHARACTER(LEN=maxchars)        :: contents
    REAL                           :: valu
    INTEGER                        :: status
    INTEGER                        :: pos, hour, minute

    CALL EditBoxReadText (hwnd, controlId, contents, maxchars)

	!	stop now if no data to convert
	pos = INDEX(contents, CHAR(0))
	IF (is_empty(contents, pos)) THEN
		IF (PRESENT(nulldefault)) argval = nulldefault
		RETURN
    END IF

	CALL CStringToFortran (contents)
    contents = ADJUSTL(contents)

	!	allow ":" as a timefield delimiter
	pos = INDEX(contents, ':')
	status = 1
	IF (pos > 0) THEN
		contents(pos:pos) = ' '
		IF (pos == 1) THEN
			hour = 0
			READ (contents, *, IOSTAT = status, END=5) minute
		ELSE	
			READ (contents, *, IOSTAT = status, END=5) hour, minute
		END IF
		IF (status == 0) THEN
			SELECT CASE (minute)
			CASE (0:59)
				argval = FLOAT(hour) + FLOAT(minute)/60.
			END SELECT
		END IF
		RETURN
	
	!	regular real value
	ELSE
		IF (INDEX(contents, '.') == 0) THEN
			pos = INDEX(contents, ' ')
			contents(pos:pos) = '.'
		END IF
		READ (contents, '(F)', IOSTAT=status, END=5) valu
		IF (status == 0) argval = valu
	END IF

5	RETURN    

END SUBROUTINE EditBoxGetReal


SUBROUTINE EditBoxSetMMSS (hwnd, controlID, argsecs)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL,    INTENT(IN)			   :: argsecs
	INTEGER                        :: minutes, seconds
	CHARACTER(LEN=14)			   :: string
	
	minutes = INT(argsecs/spm)
	seconds = INT(argsecs - spm*FLOAT(minutes))
	WRITE (string, '(I2.2, ":", I2.2)') minutes, seconds
	CALL EditBoxSetText (hwnd, controlID, string)

END SUBROUTINE EditBoxSetMMSS


SUBROUTINE EditBoxReadTime (hwnd, controlID, argval)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL, INTENT(INOUT)			   :: argval
	REAL						   :: realval
    CHARACTER(LEN=10)              :: contents
	INTEGER						   :: hour, minute
	INTEGER						   :: ios, nc

	contents = EditBoxGetText(hwnd, controlId, 10)
	nc = leftpack (contents)
			
	!	if a dp was entered, read as float
	IF (INDEX(contents(1:nc), '.') > 0) THEN
		READ (contents(1:nc), '(F)', IOSTAT=ios), realval
		IF (ios == 0) argval = realval

	ELSE
		ios = 1
		DO WHILE (ios > 0)
			ios = INDEX (contents(1:nc),':')
			IF (ios > 0) contents(ios:ios) = ","
		END DO		
		READ (contents(1:nc), '(2I)', IOSTAT=ios) hour, minute
		
		!	only return a new value if the read succeeds
		IF (ios == 0 .AND. minute >= 0 .AND. minute <= 59)	&
			argval = FLOAT(hour) + FLOAT(minute)/60.
	END IF

END SUBROUTINE EditBoxReadTime


SUBROUTINE EditBoxSetText (hwnd, controlID, text)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)     :: hwnd
    INTEGER, INTENT(IN)             :: controlID
    CHARACTER(LEN=*), INTENT(INOUT) :: text
    INTEGER                         :: rval, nc

	! ensure proper termination to prevent overruns
	IF (INDEX(text, CHAR(0)) == 0) THEN
		nc = MIN0(LEN(text),1+LEN_TRIM(text))
		text(nc:nc) = CHAR(0)
	END IF

    rval = SendControlMessage (hwnd, controlId, WM_SETTEXT, 0, LOC(text))

    IF (rval /= TRUE) THEN
        CALL ControlError ("EditBoxSetText", controlID, "WM_SETTEXT")
    END IF

END SUBROUTINE EditBoxSetText


SUBROUTINE EditBoxClear (hwnd, controlID)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)     :: hwnd
    INTEGER, INTENT(IN)             :: controlID
    INTEGER                         :: rval
	CHARACTER(LEN=1), PARAMETER		:: text = CHAR(0)

    rval = SendControlMessage (hwnd, controlId, WM_SETTEXT, 0, LOC(text))

    IF (rval /= TRUE) THEN
        CALL ControlError ("EditBoxClear", controlID, "WM_SETTEXT")
    END IF

END SUBROUTINE EditBoxClear



SUBROUTINE EditBoxSetInteger (hwnd, controlID, valu)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    INTEGER, INTENT(IN)            :: valu
    CHARACTER(LEN=40)              :: text

    WRITE (text, '(I0,A)') valu, CHAR(0)
	text = ADJUSTL(text)
    CALL EditBoxSetText (hwnd, controlID, text)

END SUBROUTINE EditBoxSetInteger


!
! Sets the contents of an edit box with an integer formatted
! as a hexadecimal number.
!
!SUBROUTINE EditBoxSetHex (hwnd, controlID, value)
!    IMPLICIT NONE 
!    INTEGER(HANDLE), INTENT(IN)    :: hwnd
!    INTEGER, INTENT(IN)            :: controlID
!    INTEGER, INTENT(IN)            :: value
!    CHARACTER(LEN=40)              :: text
!
!    WRITE (text, '(Z0,A)') value, CHAR(0)
!	 text = ADJUSTL(text)
!    CALL EditBoxSetText(hwnd, controlID, text)
!
!END SUBROUTINE EditBoxSetHex


SUBROUTINE EditBoxSetReal (hwnd, controlID, valu, width, decimalPlaces)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    REAL,    INTENT(IN)            :: valu
    INTEGER, INTENT(IN), OPTIONAL  :: width
    INTEGER, INTENT(IN), OPTIONAL  :: decimalPlaces
    CHARACTER(LEN=40)              :: text

	IF (valu /= unmeasured) THEN
		IF(PRESENT(width) .AND. PRESENT(decimalPlaces)) THEN
			WRITE (text, "(F.)") valu
		ELSE
			WRITE (text, '(F10.3, A)') valu, CHAR(0)
		END IF
    ELSE
		text = CHAR(0)
	END IF
    CALL EditBoxSetText (hwnd, controlID, text)
END SUBROUTINE EditBoxSetReal
[/cpp]

View solution in original post

0 Kudos
20 Replies
DavidWhite
Valued Contributor II
747 Views
Can I suggest that you look at the excellent set of libraries managed by Jugoslav Dujic at https://xeffort.com

These may give you a simpler way of accessing dialog boxes and setting up your program. They are fully integrated with Visual Studio.

David
0 Kudos
Paul_Curtis
Valued Contributor I
751 Views

1. Fortran is far from dead, and can easily be used for Win32 programs featuring any GUI feature, but to do this you need to learn the Win32 message-pump architecture (for which you study Petzold, not Lawrence), and write complete Win32 code in which you explicitly handle your own message loops (ie, forget Quickwin). And, by the way, 1988-93 is not even remotely ancient and you are not the only one who lugged a Compaq Plus around the globe.

2. COMMON is obsolete. Put your proc function (ie the message-loop handler called by Windows when your dialog is interacted with) in a module wherein all your required variables are module-local and thus available to your proc, which of course has only the canonical four Win32 integer arguments.

3. Your dialog proc begins (ie, WM_INITDIALOG) by loading the current values of the variables into the Editbox controls, and ends (WM_COMMAND ... ID_OK) by reading the (possibly modified) values back from those edit boxes. Here are a few editbox-related wrapper functions to get you started; in these functions hwnd is the window handle of your dialog, and controlId is the id associated with the editbox control being modified.

[cpp]!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!
! Edit box functions
!

SUBROUTINE EditBoxReadText (hwnd, controlId, text, textLen)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    INTEGER, INTENT(IN)            :: textLen
    CHARACTER(LEN=textLen), INTENT(OUT) :: text
    INTEGER                        :: rval

    text = ""
    rval = SendControlMessage (hwnd, controlId, WM_GETTEXT, &
                               textLen, LOC(text))

	!	return value is number of characters copied
    IF (rval < 0) THEN
        CALL ControlError ("EditBoxReadText", controlId, "WM_GETTEXT")
    END IF

END SUBROUTINE EditBoxReadText


FUNCTION EditBoxGetText (hwnd, controlId, length) RESULT (text)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
    INTEGER, INTENT(IN)            :: length
    CHARACTER(LEN=length)          :: text
    CHARACTER(LEN=length)	       :: contents
    INTEGER                        :: rval, nc

    rval = SendControlMessage (hwnd, controlId, WM_GETTEXT, &
				               length, LOC(contents))

    IF (rval /= 0) THEN
        text = TRIM(contents)

		! remove garbage bytes from remainder of string
		nc = INDEX(text, CHAR(0))
		IF (nc > 0 .AND. nc < length) text(nc:) = CHAR(0)
    ELSE
        CALL ControlError ("EditBoxGetText", controlId, "WM_GETTEXT")
        text = ""
    END IF

END FUNCTION EditBoxGetText


SUBROUTINE EditBoxGetInteger (hwnd, controlId, argval, nulldefault) 
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlId
	INTEGER, INTENT(INOUT)		   :: argval
	INTEGER, INTENT(IN), OPTIONAL  :: nulldefault

    INTEGER, PARAMETER             :: len = 40
    CHARACTER(LEN=len)             :: contents
    INTEGER                        :: valu
    INTEGER                        :: status, pos

    CALL EditBoxReadText (hwnd, controlId, contents, len)

	!	stop now if no data to convert
	pos = INDEX(contents, CHAR(0))
	IF (is_empty(contents, pos)) THEN
		IF (PRESENT(nulldefault)) argval = nulldefault
		RETURN
    END IF
    CALL CStringToFortran (contents)
    READ (contents, '(I)', IOSTAT=status) valu

	!	only return a new value if the inputstring was successfully read
    IF (status == 0) argval = valu
    
END SUBROUTINE EditBoxGetInteger


!
! Returns the contents of an edit box, interpreted as a 
! hexadecimal integer.
!
!INTEGER FUNCTION EditBoxGetHex (hwnd, controlId) 
!    IMPLICIT NONE 
!    INTEGER(HANDLE), INTENT(IN)    :: hwnd
!    INTEGER, INTENT(IN)            :: controlId
!    INTEGER, PARAMETER             :: len = 40
!    CHARACTER(LEN=len)             :: contents
!    INTEGER                        :: value
!    INTEGER                        :: status
!
!    CALL EditBoxReadText (hwnd, controlId, contents, len)
!    CALL CStringToFortran (contents)
!    READ (contents, '(Z)', IOSTAT=status) value
!    IF (status == 0) THEN
!        EditBoxGetHex = value
!    ELSE
!        EditBoxGetHex = 0
!    END IF
!
!END FUNCTION EditBoxGetHex


SUBROUTINE EditBoxGetReal (hwnd, controlID, argval, nulldefault)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL,INTENT(IN),OPTIONAL	   :: nulldefault
	REAL,INTENT(INOUT)			   :: argval

    INTEGER, PARAMETER             :: maxchars = 40
    CHARACTER(LEN=maxchars)        :: contents
    REAL                           :: valu
    INTEGER                        :: status
    INTEGER                        :: pos, hour, minute

    CALL EditBoxReadText (hwnd, controlId, contents, maxchars)

	!	stop now if no data to convert
	pos = INDEX(contents, CHAR(0))
	IF (is_empty(contents, pos)) THEN
		IF (PRESENT(nulldefault)) argval = nulldefault
		RETURN
    END IF

	CALL CStringToFortran (contents)
    contents = ADJUSTL(contents)

	!	allow ":" as a timefield delimiter
	pos = INDEX(contents, ':')
	status = 1
	IF (pos > 0) THEN
		contents(pos:pos) = ' '
		IF (pos == 1) THEN
			hour = 0
			READ (contents, *, IOSTAT = status, END=5) minute
		ELSE	
			READ (contents, *, IOSTAT = status, END=5) hour, minute
		END IF
		IF (status == 0) THEN
			SELECT CASE (minute)
			CASE (0:59)
				argval = FLOAT(hour) + FLOAT(minute)/60.
			END SELECT
		END IF
		RETURN
	
	!	regular real value
	ELSE
		IF (INDEX(contents, '.') == 0) THEN
			pos = INDEX(contents, ' ')
			contents(pos:pos) = '.'
		END IF
		READ (contents, '(F)', IOSTAT=status, END=5) valu
		IF (status == 0) argval = valu
	END IF

5	RETURN    

END SUBROUTINE EditBoxGetReal


SUBROUTINE EditBoxSetMMSS (hwnd, controlID, argsecs)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL,    INTENT(IN)			   :: argsecs
	INTEGER                        :: minutes, seconds
	CHARACTER(LEN=14)			   :: string
	
	minutes = INT(argsecs/spm)
	seconds = INT(argsecs - spm*FLOAT(minutes))
	WRITE (string, '(I2.2, ":", I2.2)') minutes, seconds
	CALL EditBoxSetText (hwnd, controlID, string)

END SUBROUTINE EditBoxSetMMSS


SUBROUTINE EditBoxReadTime (hwnd, controlID, argval)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
	REAL, INTENT(INOUT)			   :: argval
	REAL						   :: realval
    CHARACTER(LEN=10)              :: contents
	INTEGER						   :: hour, minute
	INTEGER						   :: ios, nc

	contents = EditBoxGetText(hwnd, controlId, 10)
	nc = leftpack (contents)
			
	!	if a dp was entered, read as float
	IF (INDEX(contents(1:nc), '.') > 0) THEN
		READ (contents(1:nc), '(F)', IOSTAT=ios), realval
		IF (ios == 0) argval = realval

	ELSE
		ios = 1
		DO WHILE (ios > 0)
			ios = INDEX (contents(1:nc),':')
			IF (ios > 0) contents(ios:ios) = ","
		END DO		
		READ (contents(1:nc), '(2I)', IOSTAT=ios) hour, minute
		
		!	only return a new value if the read succeeds
		IF (ios == 0 .AND. minute >= 0 .AND. minute <= 59)	&
			argval = FLOAT(hour) + FLOAT(minute)/60.
	END IF

END SUBROUTINE EditBoxReadTime


SUBROUTINE EditBoxSetText (hwnd, controlID, text)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)     :: hwnd
    INTEGER, INTENT(IN)             :: controlID
    CHARACTER(LEN=*), INTENT(INOUT) :: text
    INTEGER                         :: rval, nc

	! ensure proper termination to prevent overruns
	IF (INDEX(text, CHAR(0)) == 0) THEN
		nc = MIN0(LEN(text),1+LEN_TRIM(text))
		text(nc:nc) = CHAR(0)
	END IF

    rval = SendControlMessage (hwnd, controlId, WM_SETTEXT, 0, LOC(text))

    IF (rval /= TRUE) THEN
        CALL ControlError ("EditBoxSetText", controlID, "WM_SETTEXT")
    END IF

END SUBROUTINE EditBoxSetText


SUBROUTINE EditBoxClear (hwnd, controlID)
    IMPLICIT NONE
    INTEGER(HANDLE), INTENT(IN)     :: hwnd
    INTEGER, INTENT(IN)             :: controlID
    INTEGER                         :: rval
	CHARACTER(LEN=1), PARAMETER		:: text = CHAR(0)

    rval = SendControlMessage (hwnd, controlId, WM_SETTEXT, 0, LOC(text))

    IF (rval /= TRUE) THEN
        CALL ControlError ("EditBoxClear", controlID, "WM_SETTEXT")
    END IF

END SUBROUTINE EditBoxClear



SUBROUTINE EditBoxSetInteger (hwnd, controlID, valu)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    INTEGER, INTENT(IN)            :: valu
    CHARACTER(LEN=40)              :: text

    WRITE (text, '(I0,A)') valu, CHAR(0)
	text = ADJUSTL(text)
    CALL EditBoxSetText (hwnd, controlID, text)

END SUBROUTINE EditBoxSetInteger


!
! Sets the contents of an edit box with an integer formatted
! as a hexadecimal number.
!
!SUBROUTINE EditBoxSetHex (hwnd, controlID, value)
!    IMPLICIT NONE 
!    INTEGER(HANDLE), INTENT(IN)    :: hwnd
!    INTEGER, INTENT(IN)            :: controlID
!    INTEGER, INTENT(IN)            :: value
!    CHARACTER(LEN=40)              :: text
!
!    WRITE (text, '(Z0,A)') value, CHAR(0)
!	 text = ADJUSTL(text)
!    CALL EditBoxSetText(hwnd, controlID, text)
!
!END SUBROUTINE EditBoxSetHex


SUBROUTINE EditBoxSetReal (hwnd, controlID, valu, width, decimalPlaces)
    IMPLICIT NONE 
    INTEGER(HANDLE), INTENT(IN)    :: hwnd
    INTEGER, INTENT(IN)            :: controlID
    REAL,    INTENT(IN)            :: valu
    INTEGER, INTENT(IN), OPTIONAL  :: width
    INTEGER, INTENT(IN), OPTIONAL  :: decimalPlaces
    CHARACTER(LEN=40)              :: text

	IF (valu /= unmeasured) THEN
		IF(PRESENT(width) .AND. PRESENT(decimalPlaces)) THEN
			WRITE (text, "(F.)") valu
		ELSE
			WRITE (text, '(F10.3, A)') valu, CHAR(0)
		END IF
    ELSE
		text = CHAR(0)
	END IF
    CALL EditBoxSetText (hwnd, controlID, text)
END SUBROUTINE EditBoxSetReal
[/cpp]

0 Kudos
John_N_2
Beginner
747 Views
Dear Guys:

Both answers were excellent. I flipped a coin and it came down tails, so the second answer got the points.

I will get Petzold, should be in UNI Library.

I downloaded xeffort and will try both code sets.

Thanks again.

JMN


Quoting - jm-nichols@tamu.edu1
Dear Steve:

Is Fortran dead? Whenever I mention that I use it and like it - I may as well be in a Charles Dickens novel. When I mention that Intel makes a damn fine compiler then I am just wasting my breath. I am not really seeking comments, more saying that sometimes without this site a human feels very alone. I tend to identify stongly with the Neandertahls in the National Geographic, and went into a state of ernest rage when they asked if the recreated NM should live in a zoo.

I could see the pictures - here is the Neanderthal Man and beside him is the Fortran Man - see the punch cards.

I hate motorcycles although the Zen book was ok,

Now the real question, I have some legacy code that dates from the period 1988 to 1993. It was first started on a Compaq Portable, green screen, no HD and 8086 chip. I hated every Microsoft Fortran Complier after 3.3, PowerStation was a dog on my firehydrant code and the CVF compiler was interesting. However, I like my Intel compiler, even though it has taken me several years to getg it working so I can use it with MS Studio 2008. Not the compliers fault I was just busy.

I am porting an old Sewer Design Program from DOC based screen calls to Windows. I am having a lot of trouble with the simple dialog box. I have a lot of manuals that explain a lot of the examples, including the TEMPERATURE one, which I found in a Microsoft Fortran Powerstation Manual, which is the best manual for explaining the functions.

I want to have simple data dialogs that allow me to enter integers and reals (I understand the character to real conversion using a read) in groups of 2 numbers to about 10 numbers.

I can set up the RC file, I understand the basics of the calls, but the timing of the events is really hard to follow, so my write statements either miss the data or give it to me multiple times. I tried adding files, but it just crashed on me.

So here is the code, Datum works, Plostd gives me zeros or ***********. Uisng commons was the only way I could figure out how to get my values back.

I have downloaded and played with a lot of dialog boxes, I have read the Lawrence Book, they helped with the single element dialog boxes called from WINMAIN, but these boxes are proving tricky.

A simple code for a 10 element dialog box which reads the elements into reals and ints would be agreat help if one exists?

JMN

!****************************************************************************
!
! SUBROUTINE: Datum
!
! PURPOSE: Displays the Datum Box
!
!****************************************************************************

SUBROUTINE DATUM(L)

use user32

USE IFLOGM
IMPLICIT NONE
INCLUDE 'RESOURCE.FD'


INTEGER retint,L,iret
LOGICAL retlog
character*8 text
real aht, far
TYPE (dialog) dlg

common /GROW1/ aht




EXTERNAL UpdateTemp


! Initialize.

IF ( .not. DlgInit( idd_temp, dlg ) ) THEN
text ="String"
iret = MessageBox(NULL, Text,"Error: dialog not found"C, MB_OK )

ELSE

! Set up Datum controls.
If (L .eq. 1) then
Text = '1'
ELSEIF (L .eq. 2) then
Text = '2'
ELSEIF (L .eq. 3) then
Text = '3'
ELSEIF (L .eq. 4) then
Text = '4'
ELSEIF (L .eq. 5) then
Text = '5'
ELSEIF (L .eq. 6) then
Text = '6'
ELSEIF (L .eq. 7) then
Text = '7'
endif

retlog = DlgSet( dlg, IDC_EDIT_CELSIUS, text)
CALL UpdateTemp( dlg, IDC_EDIT_CELSIUS, DLG_CHANGE)
retlog = DlgSetSub( dlg, IDC_EDIT_CELSIUS, UpdateTemp )
retlog = DlgSetSub( dlg, IDC_EDIT_FAHRENHEIT, UpdateTemp )


! Activate the modal dialog.
retint = DlgModal( dlg )
! Release dialog resources.
CALL DlgUninit( dlg )
END IF

WRITE(4,200)AHT
WRITE(3,200)AHT
200 FORMAT('AT Datum:', F10.3)


END SUBROUTINE Datum

!****************************************************************************
!
! SUBROUTINE: UpdateTemp
!
! PURPOSE: Synchronizes the values of the dialog controls
!
!****************************************************************************

SUBROUTINE UpdateTemp( dlg, control_name, callbacktype )
!DEC$ ATTRIBUTES DEFAULT :: UpdateTemp
USE DFLOGM
IMPLICIT NONE
TYPE (dialog) dlg
INTEGER control_name
INTEGER callbacktype
INCLUDE 'RESOURCE.FD'
CHARACTER(256) text
INTEGER cel, far, retint
Real far1, aht
LOGICAL retlog
! Suppress compiler warnings for unreferenced arguments.
INTEGER local_callbacktype

common /GROW1/ aht


local_callbacktype = callbacktype

SELECT CASE (control_name)
CASE (IDC_EDIT_CELSIUS)
! Celsius value was modified by the user so
! update both Fahrenheit and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT_CELSIUS, text )
READ (text, *, iostat=retint) cel



CASE (IDC_EDIT_FAHRENHEIT)
! Fahrenheit value was modified by the user so
! update both celsius and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT_FAHRENHEIT, text )
READ (text, *, iostat=retint) far1

aht=far1

END SELECT



END SUBROUTINE UpdateTemp

!****************************************************************************
!
! SUBROUTINE: UpdateTemp1
!
! PURPOSE: Synchronizes the values of the dialog controls for Plot_STD
!
!****************************************************************************

SUBROUTINE UpdateTemp1( dlg, control_name, callbacktype )
!DEC$ ATTRIBUTES DEFAULT :: UpdateTemp
USE DFLOGM
IMPLICIT NONE
TYPE (dialog) dlg
INTEGER control_name
INTEGER callbacktype
INCLUDE 'RESOURCE.FD'
CHARACTER(256) text
REAL T2,T3, T4, T22,T32,T43
Integer retint
Real far1
LOGICAL retlog
! Suppress compiler warnings for unreferenced arguments.
INTEGER local_callbacktype

common /grow2/ T2,T3,T4

local_callbacktype = callbacktype

SELECT CASE (control_name)
CASE (IDC_EDIT6)
! Celsius value was modified by the user so
! update both Fahrenheit and Scroll bar values.
retlog = DlgGet( dlg, IDC_EDIT6, text )
READ (text, *, iostat=retint) T22
retlog = DlgGet( dlg, IDC_EDIT7, text )
READ (text, *, iostat=retint)T32
retlog = DlgGet( dlg, IDC_EDIT8, text )
READ (text, *, iostat=retint)T43


END SELECT
T2=T22
T3=T32
T4=T43
END SUBROUTINE UpdateTemp1

! ****************************************************************
!
SUBROUTINE PLOSTD
!
! ****************************************************************

use user32

USE IFLOGM
IMPLICIT NONE
INCLUDE 'RESOURCE.FD'

INTEGER retint,L,iret
LOGICAL retlog
character*8 text, text2, text3
real T2,T3,T4

TYPE (dialog) dlg

common /grow2/ T2,T3,T4

EXTERNAL UpdateTemp1
OPEN(7,FILE='PLOT.STD',STATUS='UNKNOWN')
! Initialize.
IF ( .not. DlgInit( idd_dialog1, dlg ) ) THEN
text ="String"
iret = MessageBox(NULL, Text,"Error: dialog not found"C, MB_OK )

ELSE

! Set up Datum controls.

text = '200'
text2 = '1000.0'
text3 = '2.5'
retlog = DlgSet( dlg, IDC_EDIT6, text)
retlog = DlgSetSub( dlg, IDC_EDIT7, UPDATETEMP1)
retlog = DlgSetSub( dlg, IDC_EDIT8, UPDATETEMP1 )
CALL UpdateTemp1( dlg, IDC_EDIT6, DLG_CHANGE)

! Activate the modal dialog.
retint = DlgModal( dlg )
! Release dialog resources.
CALL DlgUninit( dlg )
END IF


WRITE(7,200)T2,T3,T4
200 FORMAT( F5.0,/,F5.0,/,F3.1)

CLOSE(7,STATUS='KEEP')


RETURN
END



0 Kudos
bendel_boy1
Beginner
747 Views
Remember you don't have to go down the route of a Windows look & feel program. You may find that a console application will be fine, in which case your original code may compile as-is.

When converting to a Windows environment it can be as simple to recode the interface in C# or VB.NET and keep the Fortran maths engine as a DLL. This gives you a simpler environment for developing the GUI side, keeping you out of the details of the Windows window management, and keeps much of your original work.

A third approach has been for the GUI to write to an intermediate text file, so that your Fortran code reads from the file - easy to do with a shelled program and IO redirection (the > and < stuff on the command line), and then read the file back when finished. (Detecting 'when finished') will depend upon your program - easiest is for it to close itself when done, so you just look for the windows handle - look for things like 'ShellAndWait' with Google to find suitable code.)
0 Kudos
Paul_Curtis
Valued Contributor I
747 Views
Quoting - bendel boy
Remember you don't have to go down the route of a Windows look & feel program. You may find that a console application will be fine, in which case your original code may compile as-is.

When converting to a Windows environment it can be as simple to recode the interface in C# or VB.NET and keep the Fortran maths engine as a DLL. This gives you a simpler environment for developing the GUI side, keeping you out of the details of the Windows window management, and keeps much of your original work.

A third approach has been for the GUI to write to an intermediate text file, so that your Fortran code reads from the file - easy to do with a shelled program and IO redirection (the > and < stuff on the command line), and then read the file back when finished. (Detecting 'when finished') will depend upon your program - easiest is for it to close itself when done, so you just look for the windows handle - look for things like 'ShellAndWait' with Google to find suitable code.)

This answers the OP's question: Fortran didn't quietly die of old age, it committed suicide.
0 Kudos
bendel_boy1
Beginner
747 Views
Quoting - Paul Curtis

This answers the OP's question: Fortran didn't quietly die of old age, it committed suicide.

When the 'easy programming' world went visual the marketeers decided that putting Visual in the product name would be sufficient, rather than looking to see how they would do a real visual Fortran. C++ went the same route, algthough Borland did try to provide a Delphi-style C++ environment.

But I have always seen the end result as a strength of Fortran - keep Fortran focused on its strength, and allow it to mix & match with other programming languages. I think that language fads mean that Fortran would have lost ground anyway, but its 'successor' languages have, and probbaly will, lose ground in their turn.
0 Kudos
Paul_Curtis
Valued Contributor I
747 Views
Quoting - bendel boy

When the 'easy programming' world went visual the marketeers decided that putting Visual in the product name would be sufficient, rather than looking to see how they would do a real visual Fortran. C++ went the same route, algthough Borland did try to provide a Delphi-style C++ environment.

But I have always seen the end result as a strength of Fortran - keep Fortran focused on its strength, and allow it to mix & match with other programming languages. I think that language fads mean that Fortran would have lost ground anyway, but its 'successor' languages have, and probbaly will, lose ground in their turn.

I agree that Intel, and DEC/Compaq before it, dropped the ball with respect to built-in "visual" features to facilitate direct Win32 GUI programming in Fortran (although the Win32 defines and interfaces modules are wonderfully complete now, compared to CVF). But Win32 GUI is no more complex or difficult in Fortran than in any other language, and it is immensely advantageous to have the entire program in one language, especially when clever programs with well-designed highly interactive user interfaces require tightly intermixed calculation and human-interface code -- which simply cannot be done with the suggested work-arounds in your earlier post. If Fortran needlessly cedes this capability to other languages, then it will become a relic indeed.

0 Kudos
forall
Beginner
747 Views
Quoting - Paul Curtis

I agree that Intel, and DEC/Compaq before it, dropped the ball with respect to built-in "visual" features to facilitate direct Win32 GUI programming in Fortran (although the Win32 defines and interfaces modules are wonderfully complete now, compared to CVF). But Win32 GUI is no more complex or difficult in Fortran than in any other language, and it is immensely advantageous to have the entire program in one language, especially when clever programs with well-designed highly interactive user interfaces require tightly intermixed calculation and human-interface code -- which simply cannot be done with the suggested work-arounds in your earlier post. If Fortran needlessly cedes this capability to other languages, then it will become a relic indeed.


interesting debate..

I suspect the underlying reason for fortran's decline is that in the times of Fortran-66 the main use of computers was computing, while now the main use by far is displaying/playing things, with computational uses asymptoting towards some small but stable level.

darwinian concepts mean fortran user-base is proportional to niche. the quality of standards (F-90 being released too late) just affects the speed of the transient, not the long-term equilibrium. my $0.02
0 Kudos
rase
New Contributor I
747 Views
I started with Fortran II, went on to Fortran IV, Fortran 66 to Fortran 77, on various computer architectures, operating systems and development environments, doing mainly scientific programming. It was not a big deal to transfer the Fortran programs to new processors and OS. When C gained a growing user community I took courses to learn the language. After looking deeper into the C it seemed not worthwhile to switch because I had everything in Fortran 77 what I needed. Fortran 90 and 95 provided additional features which are very handy for scientific work. For the GUIs and graphics I use a library which suits my needs. Due to the hype in the community I decided to give C++ a try a few years ago. Again I have not been convinced that C++ is an adequate replacement for Fortran, at least for my main programming tasks. The features provided for mixed programming in Fortran, IVF and MS-VS allow to call functions in other languages to avoid reinventing the wheel.

Fortran is not dead, Fortran did not commit suicide. Unfortunately Fortran lost its reputation when Microsoft ceased to support the language. Blame it on Bill Gates!
0 Kudos
Steven_L_Intel1
Employee
745 Views
I can't agree with much of this. Microsoft, in particular, had no effect on Fortran's reputation. Fortran largely fell out of favor as computing extended beyond the mathematical, scientific and engineering areas and colleges chose to teach newer (and, by inference, "better") languages such as Pascal, C, C++ and, in more recent years, Java. Meanwhile, Fortran, like COBOL, continued to evolve and maintained its place in the computing environment. It's not so much that Fortran has withered but rather programming has grown beyond the areas where Fortran excels.

That does not mean that Fortran is dead - not at all. It is still very heavily used and, unlike COBOL, has lots of new applications being written in it. But it's a bigger world out there and Fortran, as flexible as it is, isn't suitable for everything.

I think a lot of the negativeness about Fortran comes from people who have not used it in decades and/or who believe that a language that is over 50 years old can't be good anymore. Would they apply that same logic to people - are 50-year-olds of no use any more? (Maybe 20-somethings might think so...) Fortran of today barely resembles the Fortran of 1957, but the core principles remain.

As for "visual programming", you're not talking about languages, you're talking tools. There exist "drag and drop" code generators for Fortran (I think one of the GINO products does this), but I'm unconvinced that they're useful for more than toy programs.
0 Kudos
bmchenry
New Contributor II
745 Views

I'm on board with Steve and those who understand that the niche for Fortran is alive: IT'S ALIVE!!!
FORmula TRANslation is the main focus of Fortran. There are millions f lines of code which are in Fortran.
I personally manage > 40 thousand lines of code in Fortran which i'll be damned if i'm going to translate into another language! The beauty of the interoperability of programs today is choose your tool for your task.

If you are living in a house and just because there is a new air hammer available does that mean you tear down your house just to rebuild it with the newfangled tool? NO! Integrate existing code to operate in the environment required.

Meaning use visual languages for the visual aspects if they are beyond what is available in Fortran (and I disagree with Steve about 3rd party tools. I like Winteracter as I think it greatly simplifies and streamlines the integration with the evolving windows/Mac/linuix GUI)

0 Kudos
rase
New Contributor I
745 Views
Quoting - bmchenry

I like Winteracter as I think it greatly simplifies and streamlines the integration with the evolving windows/Mac/linuix GUI.

Thanks for mentioning Winteracter. I use it, too, and I agree with your view.
0 Kudos
John_N_2
Beginner
745 Views
Quoting - rase
Thanks for mentioning Winteracter. I use it, too, and I agree with your view.
Guys:

I did not mean to start a civil war, I agree with most of the sentiments expressed in one way or the other.

Fortran has a number of advantages compared to a number of other languages, and a number of disadvantages. I prefer LISP as a general language, but only an idiot would use it for a scientific program needing speed.

Fortran is great for rapid program development, I spent the day fixing a program from the late 1980's and it works a treat.

I also ordered Petzold's book. I am slowly learning to program in Windows. It would be a lot easier if the samples included some dialog box examples included with the midi example. I also prefer the old Microsoft Fortran Manual for the Powerstation because of the well written examples. I have found the samples in Intel but they are harder to find and read.

Thanks for all the replies, and like anything it takes a while to learn, but it is worth learning.

Unfortunately the input required for my programs makes it just as hard to do a console as windows program so I may as well use a windows program.

JMN


0 Kudos
Nick2
New Contributor I
745 Views

Unfortunately the input required for my programs makes it just as hard to do a console as windows program so I may as well use a windows program.


If that's the case, you may want to use some kind of text input files that the user creates. Most people using my prog prefer to write input decks by hand because then they have greater control, they can save the input file for Quality Assurance/ISO compliance, and they can often start with an old input file and just make a few small changes...And let me tell you, I've never seen anyone in production mode write an input file from scratch!

The main program then takes input filename as the argument, and does its thing.

Sure enough, we have people asking us to make "input deck designer" software. But the goal for input deck designer software is to spit out a text file and start a process (your main program), so you can use any programming language that you want. There's people who do all their GUI in Fortran, and there's people who can't resist the GUI designer and eye candy of WPF.
0 Kudos
John_N_2
Beginner
745 Views

If that's the case, you may want to use some kind of text input files that the user creates. Most people using my prog prefer to write input decks by hand because then they have greater control, they can save the input file for Quality Assurance/ISO compliance, and they can often start with an old input file and just make a few small changes...And let me tell you, I've never seen anyone in production mode write an input file from scratch!

The main program then takes input filename as the argument, and does its thing.

Sure enough, we have people asking us to make "input deck designer" software. But the goal for input deck designer software is to spit out a text file and start a process (your main program), so you can use any programming language that you want. There's people who do all their GUI in Fortran, and there's people who can't resist the GUI designer and eye candy of WPF.

i use txt files for the input, but these programs have a few points where you have to make a decision and so you need a method for asking a simple question. I can do that now with dialog boxes. I played with them for ages, until I developed a slight varient on the Celc - Fahr routine that works on ints, reals and text.

But I am stopped on writing to a child window. I want to write a string to a window that has a handle hWnd, but I am blowedif outtext or drawtext work:

what am I missing.

JMN
0 Kudos
Paul_Curtis
Valued Contributor I
745 Views
But I am stopped on writing to a child window. I want to write a string to a window that has a handle hWnd, but I am blowedif outtext or drawtext work:


See the att. file for sample code on how to create a scrolling text window
0 Kudos
John_N_2
Beginner
745 Views
Dear Paul:

Thank you very much for the code for the text window. It will save a lot of work.

without wax

John Nichols
0 Kudos
John_N_2
Beginner
745 Views
Quoting - Paul Curtis

See the att. file for sample code on how to create a scrolling text window

Dear Paul:

CreateSimpleFont:

I cannot find hide nor hair of this function anywhere in the documentation. Any ideas where I find it please?

JMN
0 Kudos
Paul_Curtis
Valued Contributor I
745 Views

Was travelling, sorry for the delay. My code sample was extracted from a large project, and I failed to note the presence of some wrapper functions which greatly facilitate Win32 programming. Here is CreateSimpleFont:

[cpp]! Creates a font with simple characteristics. The face name and size
! are provided, along with bold and italic flags. Returns a handle
! to the new font, or 0 on failure.
!
INTEGER(HANDLE) FUNCTION CreateSimpleFont (faceName, size, bold, italic)
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: faceName
INTEGER, INTENT(IN) :: size
LOGICAL, INTENT(IN) :: bold
LOGICAL, INTENT(IN) :: italic

TYPE(T_LOGFONT) :: logfont
INTEGER(HANDLE) :: hfont

logfont%lfHeight = size
logfont%lfWidth = 0
logfont%lfEscapement = 0
logfont%lfOrientation = 0
IF (bold) THEN
logfont%lfWeight = FW_BOLD
ELSE
logfont%lfWeight = FW_NORMAL
END IF
logfont%lfItalic = italic
logfont%lfUnderline = .FALSE.
logfont%lfStrikeout = .FALSE.
logfont%lfCharSet = ANSI_CHARSET
logfont%lfOutPrecision = OUT_DEFAULT_PRECIS
logfont%lfClipPrecision = CLIP_DEFAULT_PRECIS
logfont%lfQuality = DEFAULT_QUALITY
logfont%lfPitchAndFamily = IOR(DEFAULT_PITCH, FF_DONTCARE)
logfont%lfFaceName = faceName

hfont = CreateFontIndirect (logfont)

IF (hfont == NULL) THEN
! deal with error
END IF
CreateSimpleFont = hfont

END FUNCTION CreateSimpleFont
[/cpp]

0 Kudos
John_N_2
Beginner
573 Views

Thanks heaps for the routine.

I have been flying between Richmond, VA and College Station, TX so I have had some time to play with the program, I have not been on the net so i had missed your add.

Things your wife does:

1. Leaves a note on your new computer to put Adobe Photoshop elements onto the box. I had an old IE V2 copy of Elements. I can not find the box, but she is insistent and turns up her nose at GIMP.

So the husband downloads the trial version and finds out he can get the 7.0 edition for $32, online of course. Problem solved.

Things your boss does:

2. Buys you a new IVF Compiler licences once the old one runs out.

Things your colleagues do:

3. Ask the following questions on an exam:

a. How many pages in the P6 manual?
b. What is the function key in P6 to do the following ............

Students not expecting questions on P6.

JMN






0 Kudos
Reply