replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - and continues
forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

and continues

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
shah



Joined: 18 Oct 2011
Posts: 13

PostPosted: Sat Oct 29, 2011 2:45 pm    Post subject: and continues Reply with quote

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)
C
33 FORMAT(7I5,3F10.3,2I5)
44 FORMAT(//59X,'NODAL POIINT DATA'//5X,'NODE',
*3X,'NODAL D.O.F.',5X,'X-COORD.',5X,'Y-COORD.',5X,'Z-COORD.',
*6X,'NODE',3X,'NODAL DOF',5X,'X-COORD.',5X,'Y-COORD.',5X,
*'Z-COORD.',//(5X,I4,3X,6I2,3X,F10.4,3X,F10.4,3X,F10.4,3X,3X,
*I4,3X,6I2,3X,F10.4,3X,F10.4,3X,F10.4/))
55 FORMAT(I10,E10.3,2F10.4)
66 FORMAT(//57X,'MATERIAL PROPERTIES'//44X,'GROUP',7X,'YOUNGS',
*7X,'POISSON',7X,'WEIGHT',/45X,'NO.',7X,'MODULUS',8X,'RATIO',
*7X,'DENSITY'//(45X,I3,5X,F10.2,1X,F10.2,6X,F10.5))
77 FORMAT(/24X,'NODE',11X,'EQUATION NUMBERS',25X,'NODE',12X,
*'EQUATION NUMBERS'//(24X,I4,3X,6I5,20X,I4,3X,6I5/))
RETURN
END
C
C
SUBROUTINE FELIB(A,LLIB,MTOT)
IMPLICIT REAL*8(A-H,O-Z)
COMMON/DIM/N1,N2,N3,N4,N5,N6,N7,N8,N9,N10,N11,N12,N13,N14
COMMON/PAR/IND,NET,NSN,NMP,NEQ,NSKY,NEQ1,LCOUNT
COMMON/TAPES/ISTRES,NDARAY,IPR
COMMON/PRECI/ITWO
COMMON/MULT/ELMN
DIMENSION A(MTOT)
DIMENSION LLIB(7,3),LT(7)
DO 100 I=1,NET
IF(IND.NE.1)GO TO 5
READ(5,11)LTYPE,NSHAPE,(LLIB(LTYPE,J),J=1,NSHAPE)
LT(I)=LTYPE
5 LA=LT(I)
GO TO (50),LA
C 10 CALL THREDT(A,LLIB,NSHAPE,MTOT)
C GO TO 100
C 20 CALL THREDB(A,LLIB,NSHAPE,MTOT)
C GO TO 100
C 30 CALL PLANE(A,LLIB,NSHAPE,MTOT)
C GO TO 100
C 40 CALL THREDS(A,LLIB,NSHAPE,MTOT)
C GO TO 100
50 CALL PLATE(A,LLIB,NSHAPE,MTOT)
C GO TO 100
C 60 CALL SHELL(A,LLIB,NSHAPE,MTOT)
C GO TO 100
C 70 CALL BOUND(A,LLIB,NSHAPE,MTOT)
100 CONTINUE
11 FORMAT(5I5)
RETURN
END
SUBROUTINE INISKP(SK, NSIZE)
IMPLICIT REAL*8(A-H,O-Z)
DIMENSION SK(NSIZE)
DO 10 I=1,NSIZE
10 SK(I)=0.0
RETURN
END

SUBROUTINE COLUMH(CHT,ND,NED,NEQ)
IMPLICIT REAL*8(A-H,O-Z)
INTEGER CHT(NEQ),ND(NED)
C CALCULATES THE COLUMN HEIGHT S OF EACH COLUMN IN THE GLOBAL STIFFNESS MATRIX
LS=100000
DO 30 K=1,NED
IF(ND(K)) 10,30,10
10 IF(ND(K)-LS)20,30,30
20 LS=ND(K)
30 CONTINUE
DO 40 K=1,NED
II=ND(K)
IF(II.EQ.0)GO TO 40
ME=II-LS
IF(ME.GT.CHT(II))CHT(II)=ME
40 CONTINUE
RETURN
END

SUBROUTINE CADNUM(CHT,NDS,NEQ,NEQ1,NSKY,MBAND)
IMPLICIT REAL*8(A-H,O-Z)
INTEGER CHT(NEQ),NDS(NEQ1)
C CALCULATES ADDRESSES OF DIAGONAL ELEMENTS IN BANDED MATRIX WHOSE COLOUMN HEIGHTS ARE KNOWN;
C CALCULATES THE NO OF ELEMENTS IN THE GLOBAL STIFFNESS MATRIX BELOW THE SKYLINE
C
DO 10 I =1,NEQ1
10 NDS(I)=0
NDS(1)=1
NDS(2)=2
MBAND=0
IF(NEQ .EQ.1) GO TO 30
DO 20 I=2,NEQ
IF(CHT(I).GT.MBAND) MBAND=CHT(I)
20 NDS(I+1)=NDS(I)+CHT(I)+1
30 MBAND=MBAND+1
NSKY=NDS(NEQ1)-1
RETURN
END

SUBROUTINE PASSEM(SK,EK,NDS,ND,NED,NEQ1,NSKY,NUED)
IMPLICIT REAL*8(A-H,O-Z)
DIMENSION SK(NSKY),NDS(NEQ1), ND(NED),EK(NUED,NUED)
C ASSEMBLE ELEMENT STIFFNESS INTO COMPACTED GLOBAL STIFFNESS
DO 70 I=1,NED
II=ND(I)
IF(II)70,70, 30
30 CONTINUE
DO 60 J=1, NED
JJ=ND(J)
IF (JJ)60,60,40
40 CONTINUE
MI=NDS(JJ)
IJ=JJ-II
IF(JJ)60,50,50
50 KK=MI+IJ
SK(KK)=SK(KK)+EK(I,J)
60 CONTINUE
70 CONTINUE
RETURN
END

SUBROUTINE PASOLV(SK,P,NDS,NN,NEQ1,NSKY,KKK)
IMPLICIT REAL*8(A-H,O-Z)
DIMENSION SK(NSKY),P(NN),NDS(NEQ1)
IF(KKK-2) 40,150,150
40 DO 140 N=1,NN
KN=NDS(N)
KL=KN+1
KU=NDS(N+1)-1
KH=KU-KL
IF(KH) 110,90,50
50 K=N-KH
IC=0
KLT=KU
DO 80 J=1,KH
IC=IC+1
KLT=KLT-1
KI=NDS(K)
ND=NDS(K+1)-KI-1
IF(ND) 80, 80, 60
60 KK=MIN0(IC,ND)
C=0.0
DO 70 L=1, KK
70 C=C+SK(KI+L)*SK(KLT+L)
SK(KLT)=SK(KLT)-C
80 K=K+1
90 K=N
B=0.0
DO 100 KK=KL,KU
K=K-1
KI=NDS(K)
C=SK(KK)/SK(KI)
B=B+C*SK(KK)
100 SK(KK)=C
SK(KN)=SK(KN)-B
110 IF(SK(KN)) 120,120, 14
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2615
Location: Sydney

PostPosted: Mon Oct 31, 2011 1:59 am    Post subject: Reply with quote

You have left a bit off the end of this part of the dump !!

I've looked at the code. When was PASSFEM written ? Looks about 1972, based on the lines.
DIMENSION A(30000)
MTOT=30000
This indicates the memory management pedigree.
Most can be changed to ALLOCATE, although usually not all.

It pre-dates fortran 77, as there are a number of numeric IF's
The code should be fixed format. Typically the leading 6 blank characters have been striped, which is important for the * continuation lines. ( I'd recommend you convert to free format)

To provide data that can be read, you need a data file. You have not listed this. This must be provided (with an OPEN statement) for unit 5
Output is to unit 6, which can be the screen of a file.

Two other file units are referenced: NDARAY (=2) and ISTRES (=1).
These are identified by the use of REWIND, but no other reference is made to them. These are probably for binary reads and writes. The code for using these files is is not included in your listing.

When transfering to modern fortran, it is preferable to use fortran file unit numbers > 10; ( I convert 5 to 11 and 6 to 12, and would use 21 and 22 for the binary file units )

As with this version of fortran, there is mixture of double precision functions, which are now replaced by generic names.
See IMPLICIT REAL*8(A-H,O-Z)
See use of intrinsic functions MIN0,DSIN, DCOS, FLOAT and DBLE all need to be converted to fortran 90+.

There is also use of what I expect are DEC system routines, eg GETTIM.

It may be free, but it is old fortran and there is still a bit missing.
I'd suggest cleaning it to free format and using indenting for the DO loops.
Changing all the numeric if's (eg IF (NN-MN)130,125,140 ) also could be changed to make it more readable, but they still work !!

Good luck

John
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group