Silverfrost Forums

Welcome to our forums

Declaration of arrays using variables, cannot see in SDBG

19 Jul 2007 5:43 #2078

I have not been able to find answers to this in any of the forums, so I'll give it a go here.

How do I view my arrays in the debgger when I have declared then using another integer variable? I cannot see the values, only memory dumps unless I declare them using parameters. If anybody knows how this simple thing can be done I would very much appreciate it.

Martin

20 Jul 2007 4:29 #2088

Can you give an example piece of code please.

20 Jul 2007 5:39 #2090

Robert, Thanks for the reply. Sure, this is one subroutine:

SUBROUTINE WILSON (NC,X,LAMBDA,GAMMA,GAMMAL,GAMMAX) IMPLICIT REAL*8 (A-H,O-Z) DOUBLE PRECISION LAMBDA(NC,NC) DIMENSION X(NC),GAMMA(NC),GAMMAL(NC,NC,NC),GAMMAX(NC,NC),S(NC),EPS(NC,NC) DO K=1,NC S(K) = 0.D0 DO J=1,NC S(K) = S(K) + X(J)*LAMBDA(J,K) ENDDO ENDDO DO K=1,NC SUM = 0.D0 DO M=1,NC SUM = SUM + X(M)*LAMBDA(K,M)/S(M) ENDDO GAMMA(K) = 1.D0-DLOG(S(K))-SUM ENDDO RETURN END

Using these declarations for the arrays does not allow me to view the contents, I get an 'Invalid floating point number' when expanding the arrays. The arrays are declared the same way in MAIN. The program is written in f77.

Martin

21 Jul 2007 4:40 #2091

Martin,

I'm pleased to see another wilson subroutine. I am still using many from the 70's.

I'm drawn to reply to this as I am also having repeated problems with infrequent use of SDBG with FTN95 Ver 4.9.1. There appear to be a number of other recent possibly unrelated problems. Frequently when I start SDBG, nothing appears and I have to maximise, exit then restart to get the windows to appear... I think it's a problem with the SDBG configuration file being repeatedly corrupted.

Anyway, I tried your example with FTN95 Ver 4.9.1 and also Ver 4.00, which I have on a very old machine.

In Ver 4.00, SDBG reported arrays S and EPS as pointers, but did not display their values corectly. In ver 4.9.1, they are reported as arrays, but again I could not view their values. I put a breakpoint at the second set of do loops, but the reported values of S were undefined. It did not crash.

So both SDBG do not corectly display the local automatic arrays.

I also changed your code to 'clean it up'. I prefer the use of LOG rather than DLOG, as this uses the generic function name, which saves on possible errors when changing KIND. I also use /implicit_none to confirm all variable declarations.

integer4, parameter :: nc = 4 real8 X(NC), LAMBDA(NC,NC), GAMMA(NC), GAMMAL(NC,NC,NC), GAMMAX(NC,NC) ! lambda = 1 x = 1 call WILSON (NC,X,LAMBDA,GAMMA,GAMMAL,GAMMAX) end

SUBROUTINE WILSON (NC,X,LAMBDA,GAMMA,GAMMAL,GAMMAX) ! integer4 nc real8 X(NC), LAMBDA(NC,NC), GAMMA(NC), GAMMAL(NC,NC,NC), GAMMAX(NC,NC) ! integer4 K, J, M real8 sum, S(NC),EPS(NC,NC) real8, parameter :: zero = 0 real8, parameter :: one = 1

DO K=1,NC sum = zero DO J=1,NC sum = sum + X(J)*LAMBDA(J,K) END DO S(K) = sum END DO

DO K=1,NC SUM = zero DO M=1,NC SUM = SUM + X(M)*LAMBDA(K,M)/S(M) END DO GAMMA(K) = one - LOG (S(K)) - SUM END DO RETURN END

22 Jul 2007 1:43 #2095

John, I find that the Wilson model is still one of the best AC models out there for VLE, it's definitely one of the simplest in use. 😄 Thanks for the tips regarding the clean up of the code, though I left the DLOG there.

Using IMPLICIT NONE and subsequently declaring the variables, I'm still not able to view the content of local arrays. Arrays passed on (i.e. in the subroutine call) is not a problem, but local arrys appear as 'invalid floating points', even though their values are real (and correct!). I'm compiling using FTN95 5.1 and the debugger tools provided from this forum for Win Vista. I experienced the same problems under Win XP.

The code below is the current status of the subroutine, though I have omitted a large portion, since the content of this is not relevant in this discussion.

      SUBROUTINE WILSON (NC,X,LAMBDA,GAMMA,GAMMAL,GAMMAX)
      IMPLICIT NONE
      REAL*8 LAMBDA(NC,NC),X(NC),GAMMA(NC),GAMMAL(NC,NC,NC),S(NC),
     & EPS(NC,NC),GAMMAX(NC,NC),P,SUM,ZERO,ONE
      INTEGER NC,I,J,K,M,N
      ZERO = 0.D0
      ONE  = 1.D0
C
CCC   ACTIVITY COEFFICIENTS
C
      DO K=1,NC
        SUM = ZERO
        DO J=1,NC
            SUM = SUM + X(J)*LAMBDA(J,K)
        ENDDO
        S(K) = SUM
      ENDDO
      DO K=1,NC
        SUM = ZERO
        DO M=1,NC
          SUM = SUM + X(M)*LAMBDA(K,M)/S(M)
        ENDDO
        GAMMA(K) = ONE-DLOG(S(K))-SUM
      ENDDO
     RETURN
     END

Does anybody have an idea on how to solve this peculiar problem?! I cannot see the content of arrays 'S' and 'EPS'.

Martin

22 Jul 2007 4:40 #2096

Martin,

What is the value of NC used to size your arrays ? As I have experienced problems with SDBG that you describe when arrays have been very large. When dynamic arrays are declared with much smaller values the problems go away. Of course this is very frustrating when it is not possible to duplicate the original bug using much smaller data sets !

Just a thought.

cheers John

22 Jul 2007 4:56 #2097

NC=3, so it should not pose a problem with the array size.

Please login to reply.