- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This is the line that crashes when I run the code in debug mode:
HMX = HMX*HMX2SM
Here is the context of the Fortran line above:
SUBROUTINE IOCBCO2SM(T, P, HMX, DHMX)
!========================
! DESCRIPTION OF VARIABLES
!
! T: TEMPERATURE
! P: PRESSURE
! HMX: MOLAR ENTHALPY
! DHMX: MOLAR HEAT CAPACITY
!=============================
! DECLARING VARIABLES
!
DOUBLE PRECISION T, P, HMX, DHMX
!=======================
! INCLUDING IO DATA CONVERSION PARAMETERS
!
INCLUDE 'IOPARAM.FOR'
!===========================
! CONVERTING DATA DEPENDING ON MODEL
!
T = T*TA2SM + TB2SM
P = P*P2SM
HMX = HMX*HMX2SM
DHMX = DHMX*DHMX2SM
!--------------------------------------
! RETURN TO INTERFACE ROUTINE
!
RETURN
END
---------------------------------------------------
File IOPARAM.FOR looks as follows (I have removed some lines):
!
! DECLARING PARAMETERS
!
!*********************
!-------------------
! CO UNIT: mol/s, SM UNIT: mol/s
DOUBLE PRECISION, PARAMETER :: NF2SM = 1D0
! CO UNIT: Pa, SM UNIT: Pa
DOUBLE PRECISION, PARAMETER :: P2SM = 1D0
! CO UNIT: K, SM UNIT: K
DOUBLE PRECISION, PARAMETER :: TA2SM = 1D0, TB2SM = 0.0
!
! DATA FOR CONVERSION BETWEEN SIMULATION MANAGER AND CAPE-OPEN FOR CALL-BACK TO
! THERMODYNAMIC ROUTINES.
!
!------------------------------
! CO UNIT: J/mol, SM UNIT: J/MOL
DOUBLE PRECISION, PARAMETER :: HMX2SM = 1D0
! CO UNIT: J/(mol*K), SM UNIT: J/(mol*K)
DOUBLE PRECISION, PARAMETER :: DHMX2SM = 1D0
!
!**** END OF FILE: IOPARAM.FOR ***
---------------------
Why does this particular line crash? Why not the line above it?? Or the line below it??
-Bernt
HMX = HMX*HMX2SM
Here is the context of the Fortran line above:
SUBROUTINE IOCBCO2SM(T, P, HMX, DHMX)
!========================
! DESCRIPTION OF VARIABLES
!
! T: TEMPERATURE
! P: PRESSURE
! HMX: MOLAR ENTHALPY
! DHMX: MOLAR HEAT CAPACITY
!=============================
! DECLARING VARIABLES
!
DOUBLE PRECISION T, P, HMX, DHMX
!=======================
! INCLUDING IO DATA CONVERSION PARAMETERS
!
INCLUDE 'IOPARAM.FOR'
!===========================
! CONVERTING DATA DEPENDING ON MODEL
!
T = T*TA2SM + TB2SM
P = P*P2SM
HMX = HMX*HMX2SM
DHMX = DHMX*DHMX2SM
!--------------------------------------
! RETURN TO INTERFACE ROUTINE
!
RETURN
END
---------------------------------------------------
File IOPARAM.FOR looks as follows (I have removed some lines):
!
! DECLARING PARAMETERS
!
!*********************
!-------------------
! CO UNIT: mol/s, SM UNIT: mol/s
DOUBLE PRECISION, PARAMETER :: NF2SM = 1D0
! CO UNIT: Pa, SM UNIT: Pa
DOUBLE PRECISION, PARAMETER :: P2SM = 1D0
! CO UNIT: K, SM UNIT: K
DOUBLE PRECISION, PARAMETER :: TA2SM = 1D0, TB2SM = 0.0
!
! DATA FOR CONVERSION BETWEEN SIMULATION MANAGER AND CAPE-OPEN FOR CALL-BACK TO
! THERMODYNAMIC ROUTINES.
!
!------------------------------
! CO UNIT: J/mol, SM UNIT: J/MOL
DOUBLE PRECISION, PARAMETER :: HMX2SM = 1D0
! CO UNIT: J/(mol*K), SM UNIT: J/(mol*K)
DOUBLE PRECISION, PARAMETER :: DHMX2SM = 1D0
!
!**** END OF FILE: IOPARAM.FOR ***
---------------------
Why does this particular line crash? Why not the line above it?? Or the line below it??
-Bernt
Link Copied
5 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It will be easier to offer help if you first post code using HTML tags as follows:
Replace [] with <> to get it to work. I have used []
because I am not posting code. HTH
code here
Replace [] with <> to get it to work. I have used []
because I am not posting code. HTH
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Take a look at the calling code. I bet that the actual 3rd argument (HMX) is a constant (literal or parameter). You mustn't do that -- you were trying to modify the value of the constant, which is a no-no. You have to make a temporary either in caler or in the callee. Luckily, CVF 6.x does raise an access violation on these -- what a coincidence, I've just been debugging such lint on 5.0D which didn't cause a run-time error, but, far worse run-time misbehaviour.
Jugoslav
Jugoslav
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
SUBROUTINE IOCBCO2SM(HMX)
DOUBLE PRECISION HMX
DOUBLE PRECISION, PARAMETER :: HMX2STD = 1
HMX = HMX*HMX2SM
RETURN
END SUBROUTINE
As is seen, HMX is not a constant/a parameter.
However, I call the subroutine like this:
CALL IOCBCO2SM(1D0)
Queston: Does this *effectively* make the argument a constant?
-Bernt
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, 100 is a constant (it is literal (unnamed) constant as opposed to parameter, which is a named constant). You mustn't modify 100. Approximately, this "100" compiler translates as an entry in a table physically located in .exe, which is loaded into memory when executed. Since Windows doesn't allow self-modifying programs, it protects this piece of memory from writing; thus the crash.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Actually, Windows does allow self-modifying programs and CVF even creates them. Here is a disassembly of the code for subroutine set_params in my first post to the thread "two interfaces for the same routine?" in comp.lang.fortran:
Careful analysis reveals that it creates the code sequence:
at [ebp-16] and then pushes the address of the created routine on the stack. CVF does in fact create read-only handles to constants, which is a very good thing, but the mechanism has nothing to do with a prohibition on self-modifying programs, because there is no such prohibition.
_COMPUTE_MOD_mp_SET_PARAMS@16 PROC push ebp mov ebp, esp sub esp, 32 lea ecx, dword ptr _FUN$0002@4 ; 000030 mov eax, dword ptr 8[ebp] ; 000006 mov edx, dword ptr 12[ebp] mov dword ptr -15[ebp], ecx ; 000030 mov dword ptr -10[ebp], ebp fld qword ptr [eax] ; 000028 mov byte ptr -16[ebp], 185 ; 000030 fstp qword ptr -24[ebp] ; 000028 mov byte ptr -11[ebp], 184 ; 000030 fld qword ptr [edx] ; 000029 lea edx, dword ptr -16[ebp] ; 000030 fstp qword ptr -32[ebp] ; 000029 mov word ptr -6[ebp], 57855 ; 000030 push edx push dword ptr 16[ebp] call dword ptr 20[ebp] ; 38 end subroutine set_params mov esp, ebp ; 000038 pop ebp ret 16 _COMPUTE_MOD_mp_SET_PARAMS@16 ENDP
Careful analysis reveals that it creates the code sequence:
mov ecx, {address of _FUN$0002@4} mov eax, {stack frame pointer of _COMPUTE_MOD_mp_SET_PARAMS@16} jmp ecx
at [ebp-16] and then pushes the address of the created routine on the stack. CVF does in fact create read-only handles to constants, which is a very good thing, but the mechanism has nothing to do with a prohibition on self-modifying programs, because there is no such prohibition.

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page