Silverfrost Forums

Welcome to our forums

help me to understand this

20 Oct 2011 12:04 #9106

there are no errors in programme but with few warnings & after clicking compiling button it shows the following msg

***** SUBROUTINE 'PASSIN' called with argument no 7 as a REAL(KIND=2) when a INTEGER(KIND=3) was expected (from the main program)**

& then the Compilation failed.

what ot do? (where SUBROUTINE 'PASSIN' is the subroutine of the main programme)

20 Oct 2011 12:38 (Edited: 21 Oct 2011 9:01) #9108

can u plz tell me elaborately the meaning of argument 7. i am still unable to understant tne meaning of argument 7 if possible plz explain with an example. may be because of this m unable to sort out the problem...

20 Oct 2011 1:49 #9109

If you had

CALL passin(x1, x2, etc)

then x1 is the first 'argument' and so on.

Apparently argument number 7 has the wrong TYPE. It is REAL when an INTEGER is expected.

You will have to show us the lines of code that have CALL passin(... to make sense of this. Also the first few lines of SUBROUTINE passin(...

21 Oct 2011 7:32 (Edited: 21 Oct 2011 9:00) #9110

ok.so heres the full subroutine progamme:

  SUBROUTINE PASSIN(X,Y,Z,E,PR,WD,NDF,NSN,NMP,NEQ) 
  IMPLICIT REAL*8(A-H,O-Z)
  COMMON/PRECI/ITWO     
  COMMON/TAPES/ISTRES,NDARAY,IPR
  DIMENSION X(NSN),Y(NSN),Z(NSN),E(NMP),PR(NMP),WD(NMP)
  DIMENSION NDF(6,NSN),JF(6)
  DIMENSION NCYLT(1000)
  FLOAT(I)=DBLE(I)
  MN=0

100 READ(5,33)NN,(JF(I),I=1,6),X(NN),Y(NN),Z(NN),NI,NCYL NCYLT(NN)=NCYL N=MN+NI MN=MN+1 110 DO 120 I=1,6 NDF(I,NN)=JF(I) 120 CONTINUE IF (NI.EQ.0) GO TO 130 IF (NN-MN)130,125,140 125 CONTINUE IF(NSN-NN)170,170,100 130 MN=NN
GO TO 125 C C AUTOMATIC GENERATION OF NODAL DATA C 140 NX=(NN-N+NI)/NI XD=(X(NN)-X(N-NI))/FLOAT(NX) YD=(Y(NN)-Y(N-NI))/FLOAT(NX) ZD=(Z(NN)-Z(N-NI))/FLOAT(NX) MN=NN 150 X(N)=X(N-NI)+XD Y(N)=Y(N-NI)+YD Z(N)=Z(N-NI)+ZD NCYLT(N)=NCYLT(NN) DO 160 I=1,6 NDF(I,N)=JF(I) 160 CONTINUE N=N+NI IF(N.LT.NN) GO TO 150 IF(NSN-NN)170,170,100 170 CONTINUE DO 180 I=1,NSN IF(NCYLT(I).EQ.0) GO TO 180 THETA=Y(I)*3.14159/180.0 Y(I)=X(I)*DSIN(THETA) Y(I)=X(I)*DCOS(THETA) 180 CONTINUE IF(IPR.EQ.0)WRITE(6,44)(I,(NDF(J,I),J=1,6),X(I),Y(I),Z(I),I=1,NSN) C CONVERT '0' & '1' OF 'NDF' ARRAY TO EQUATION NUMBERS & '0'S. NEQ=0 DO 30 N=1,NSN DO 30 I=1,6 IF(NDF(I,N))10,20,10 20 NEQ=NEQ+1 NDF(I,N)=NEQ GO TO 30 10 NDF(I,N)=0 30 CONTINUE IF(IPR.EQ.0)WRITE(6,77)(I,(NDF(J,I),J=1,6),I=1,NSN)

C READ & PRINT MATERIAL PROPERTIES DO 1 J=1,NMP 1 READ(5,55)I,E(I),PR(I),WD(I) WRITE(6,66)(I,E(I),PR(I),WD(I),I=1,NMP)

[color=red:6a7731d8f8]& thanx for your valuable advice,[/color:6a7731d8f8] & if u also find some problem with this subroutine plz let me know.. i will also now try to eliminate the error shown to me.

21 Oct 2011 7:58 #9111

[color=red:7a70a2a645]& heres the call of the above sub routine[/color:7a70a2a645]: CALL PASSIN (A(N2),A(N3),A(N4),A(N5),A(N6),A(N7),A(N1), *NSN,NMP,NEQ)

21 Oct 2011 8:09 #9112

So the 7th argument is defined as INTEGER but is REAL in the call.

21 Oct 2011 8:48 #9113

Just a remark:

You should always use IMPLICIT NONE (and never things like IMPLICIT REAL ...).

Doing this, you help the compiler to find errors, and you force yourself to make explicit definitions of all of your variables.

Regards - Wilfried

21 Oct 2011 10:55 #9114

Wilfried, I doubt very much that this is newly written code, it is almost certainly legacy code from the 70's or 80's when the use of IMPLICIT REAL*8(A-H,O-Z) was common place.

I for one have never used IMPLICIT NONE but continue to use IMPLICIT DOUBLE PRECISION and I know that I am not alone in these fora to do this. It doesn't cause me any problems

22 Oct 2011 12:59 #9115

*** SUBROUTINE 'PASSIN' called with argument no 7 as a REAL(KIND=2) when a INTEGER(KIND=3) was expected (from the main program)

This is a mixed mode warning message, as when PASSIN was called, array NDF(6,NSN) was supplied memory in the array A from position (N1). This is a warning message.

& then the Compilation failed.

is due to some other problem.

To remove the mixed mode error, use /error_numbers compilation option and then you can use /ignore nnn to ignore this warning. See the help for more info. You can place these compilation options in a file ftn95.cfg. I use /ERROR_NUMBERS /IMPLICIT_NONE /INTL /LOGL

I tried the following example (fea.f95) with: ftn95 fea /error_numbers then ftn95 fes /error_numbers /ignore 676 This compiles ok. Note that 676 is only a warning and does not cause the compiler to fail.

     real*8    aa(10000)
     integer*4 n1,n2,n3,n4,nn,ne,neq
!
     nn = 100
     ne = 100
     n1 = 1
     n2 = n1 + nn*3
     n3 = n2 + nn*3
     n4 = n3 + ne*6
!
     call dout (aa(n1), aa(n2), aa(n3), aa(n4), nn, ne, neq)
     end

     subroutine dout (cord, jteqn, elcon, eqband, nn, ne, neq)
!
     integer*4 nn, ne, neq,  n
     integer*4 jteqn(6,nn), elcon(12,ne), eqband(*)
     real*8   cord(3,nn)
!
     do n = 1,nn
        cord(:,n) = 0
     end do
     end

john

24 Oct 2011 6:54 #9117

To remove the mixed mode error, use /error_numbers compilation option and then you can use /ignore nnn to ignore this warning. See the help for more info. You can place these compilation options in a file ftn95.cfg. I use /ERROR_NUMBERS /IMPLICIT_NONE /INTL /LOGL

hey i guess, ur explanation is good,but i didnt get ur above explanation on removal of mixed mode error.plz elaborately explain the above.specially how to create or input

You can place these compilation options in a file ftn95.cfg. I use /ERROR_NUMBERS /IMPLICIT_NONE /INTL /LOGL [b]

plz do exlain this...

24 Oct 2011 2:17 #9121

We also have (many lines of) legacy code where implicit statements are common. Since I prefer to use implicit none (as Wilfried suggests) I often use SPAG which has an option to explicitly defines variables. It is actualy a restructuring tool with a lot of useful options!

Please login to reply.