Sie sind auf Seite 1von 19

C---------------------------------------------------------------------- BEM00010

SUBROUTINE APPEL(X,Z,ZKQG,ZKUG,ZKQL,ZKUL,PG,ZKG,PU,PQ,C,LXZI,
BEM00020
.
MDELEM,VN1,VN2,VN3,VN4,NADR,MADR,VWORK,IWORK,NPROB)BEM00030
C-----------------------------------------------------------------------BEM00040
C0 APPELF
APPEL
BEM00050
C1 PURPOSE
Performs the main stages of the BEM by calling the
BEM00060
C1
corresponding modules
BEM00070
C2 CALL
CALL APPEL(X,Z,ZKQG,ZKUG,ZKQL,ZKUL,PG,ZKG,PU,PQ,C,LXZI,
BEM00080
C2
MDELEM,VN1,VN2,VN3,VN4,NADR,MADR,VWORK,IWORK,NPROB) BEM00090
C3 CALL ARG. X(NOM),Z(NOM)
= Coordinates of discretization nodes BEM00100
C3
LXZI(NOM)
= Addresses of possible double nodes BEM00110
C3
NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM00120
C3
MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR,
BEM00130
C3
NINTS,NSIDE)
BEM00140
C3
C(NOM)
= Coefficients c incase of dir. comp. BEM00150
C3
ZKQL(NOM,NNODE)
= Local Kq matrix
BEM00160
C3
ZKUL(NOM,NNODE)
= Local Ku matrix
BEM00170
C3
ZKQG(NOM,NOM)
= Global Kq matrix
BEM00180
C3
ZKUG(NOM,NOM)
= Global Ku matrix
BEM00190
C3
ZKG(NOM,NOM),PG(NOM)= Global system matrix and vector
BEM00200
C3
PU(NOM),PQ(NOM)
= Boundary values of u and q
BEM00210
C3
VN1(N1),VN2(N2)
= Boundary conditions on N1, N2
BEM00220
C3
VN3(N3),VN4(N4)
= Boundary conditions on N3, N4
BEM00230
C3
VWORK(3*NOM)
= Working vector for k(2) comput.
BEM00240
C3
IWORK(NOM)
= Working vector for k(2) comput.
BEM00250
C3
NOM,NELEM
= Discr. nb. of nodes and elements
BEM00260
C3
NOMM,NELMM
= Discr. max nb. of nodes and elementsBEM00270
C3
ILISS
= Mode of C computation (0/1)
BEM00280
C3
NNODM
= Discr. max nb. of nodes per element BEM00290
C3
XLOC(NNODE)
= X-coordinates of element IE nodes
BEM00300
C3
ZLOC(NNODE)
= Z-coordinates of element IE nodes
BEM00310
C3
NODE(NNODE)
= Nodes of element IE
BEM00320
C3
NINTR,NINTS
= Nb. of regular and singular int. ptsBEM00330
C3
N1,N2,N3,N4
= Nb. of nodes of bound. 1,2,3,4
BEM00340
C3
IO5,IO6,NSAVE
= Input,output and save file numbers BEM00350
C3
ISAVE
= Save results and postprocess (1)
BEM00360
C3
ICOND
= Compute cond. number k(2)
(1)
BEM00370
C3
RCOND
= Condition number k(2)
BEM00380
C3
NPROB
= Nmber of problems to be solved
BEM00390
C4 RET. ARG. PU,PQ...
BEM00400
C6 INT.CALL INPUTD,BEMK,ASSEMK,ASSEMP,DBNOD,CONDNO,SOLVE,SORT,OUTPUT, BEM00410
C6
ERRORS
BEM00420
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM00430
CLAPPEL SUB. WHICH PERFORMS THE MAIN STAGES OF THE 2D-BEM
BEM00440
C-----------------------------------------------------------------------BEM00450
C
BEM00460
IMPLICIT REAL*8(A-H,O-Z)
BEM00470
C
BEM00480
PARAMETER (NNODMP=4)
BEM00490
C
BEM00500
INTEGER *2 NADR(NOM),MADR(NOM)
BEM00510
C
BEM00520
COMMON /MAILLE/ NOMM,NELMM,NOM,NELEM,NNODM,N1,N2,N3,N4,I1,I2,
BEM00530
.
I3,I4,ILISS,ISAVE,IO5,IO6,NSAVE
BEM00540
COMMON /DELEM/ XLOC(NNODMP),ZLOC(NNODMP),NODE(NNODMP),
BEM00550
.
NNODE,NINTR,NINTS,NSIDE
BEM00560
C
BEM00570
C.....Problem matrices and vectors
BEM00580
C
BEM00590
DIMENSION ZKQG(NOMM,NOM),ZKUG(NOMM,NOM),ZKQL(NOMM,NNODM),
BEM00600
.
ZKUL(NOMM,NNODM),ZKG(NOMM,NOM),PG(NOM),PU(NOM),PQ(NOM), BEM00610
.
VN1(N1),VN2(N2),VN3(N3),VN4(N4),VWORK(3*NOM),IWORK(NOM) BEM00620
C
BEM00630
C.....Domain geometry and topology
BEM00640
C
BEM00650
DIMENSION X(NOM),Z(NOM),C(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM)
BEM00660
C
BEM00670
DATA ZERO/0.D0/,ONE/1.D0/
BEM00680
C
BEM00690
C=====General loop on the problems
BEM00700
C
BEM00710
DO IPROB=1,NPROB
BEM00720
C
BEM00730
C........Input of general data, analysis of boundary, double nodes,
BEM00740
C
Initial conditions
BEM00750
C
BEM00760

C
C

CALL INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR,ICOND)
---------IF (ISAVE.EQ.1) THEN
REWIND NSAVE
END IF

C
C........Formation of the matrices Ku and Kq, and system matrix K
C
CALL BEMK(ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR,MADR)
C
--------C
C........Assembling of the general system matrix ZKG
C
CALL ASSEMK(ZKG,ZKUG,ZKQG,NADR)
C
----------C
C........Construction of the system right hand side PG
C
CALL ASSEMP(PG,ZKUG,ZKQG,NADR,VN1,VN2,VN3,VN4)
C
----------C
C........Double nodes compatibility conditions on ZKG and PG
C
CALL DBNOD(ZKG,PG,VN1,NADR,LXZI)
C
---------C
C........Condition number computation if ICOND=1
C
(!: ZQUG and ZKQG are working matrix from now)
C
CALL CONDNO(ZKG,ZKUG,ZKQG,VWORK,IWORK,ICOND,RCOND)
C
----------C
C........Solving of the system
C
CALL SOLVE(ZKG,PG,1)
C
---------C
C........Sort results
C
CALL SORT(PG,PU,PQ,VN1,VN2,VN3,VN4,NADR)
C
--------C
C........Post process and print results from Laplace' solution.
C
CALL OUTPUT(PU,PQ,X,Z,MDELEM,ICOND,RCOND)
CALL OUT2(PU,PQ,X,Z,MDELEM,ICOND,RCOND)
C
C

-----------

BEM00770
BEM00780
BEM00790
BEM00800
BEM00810
BEM00820
BEM00830
BEM00840
BEM00850
BEM00860
BEM00870
BEM00880
BEM00890
BEM00900
BEM00910
BEM00920
BEM00930
BEM00940
BEM00950
BEM00960
BEM00970
BEM00980
BEM00990
BEM01000
BEM01010
BEM01020
BEM01030
BEM01040
BEM01050
BEM01060
BEM01070
BEM01080
BEM01090
BEM01100
BEM01110
BEM01120
BEM01130
BEM01140
BEM01150
BEM01160
BEM01170
BEM01180
BEM01190
BEM01200
BEM01210
BEM01220
BEM01220

BEM01230
BEM01240
END DO
BEM01250
C
BEM01260
RETURN
BEM01270
C
BEM01280
END
BEM01290
C-----------------------------------------------------------------------BEM01300
SUBROUTINE INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR,ICOND) BEM01310
C-----------------------------------------------------------------------BEM01320
C0 INPUTF
INPUT
BEM01330
C1 PURPOSE
Reads the general datas for the 2D-BEM, i.e. the nodes
BEM01340
C1
coord.,elements definition, integrat. and B.C. informationBEM01350
C2 CALL
CALL INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR)
BEM01360
C3 (CALL ARG. X(NOM),Z(NOM)
= Coordinates of discretization nodes BEM01370
C3 (RET.
LXZI(NOM)
= Addresses of possible double nodes BEM01380
C3
NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM01390
C3
MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR,
BEM01400
C3
NINTS,NSIDE)
BEM01410
C3
VN1(N1),VN2(N2)
= Boundary conditions on N1, N2
BEM01420
C3
VN3(N3),VN4(N3)
= Boundary conditions on N3, N4
BEM01430
C3
NOM,NELEM
= Discr. nb. of nodes and elements
BEM01440
C3
NOMM,NELMM
= Discr. max nb. of nodes and elementsBEM01450
C3
NNODM
= Discr. max nb. of nodes per element BEM01460
C3
NNODE,NSIDE
= Current nb. of nodes and code of el.BEM01470
C3
NINTR,NINTS
= Nb. of regular and singular int. ptsBEM01480
C3
N1,N2,N3,N4
= Nb. of nodes of bound. 1,2,3,4
BEM01490
C3
IO5,IO6,NSAVE
= Input,output and save file numbers BEM01500

C3
ISAVE
= Save results and postprocess (1)
BEM01510
C3
ICOND
= Compute cond. number k(2)
(1)
BEM01520
C6 INT.CALL ERRORS
BEM01530
CE ERRORS
01= General data are out of range
BEM01540
CE
02= Element nodes are out of range
BEM01550
CE
03= End of data in input file
BEM01560
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM01570
CLINPUT SUB. WHICH READS INPUT DATA FOR THE 2D-BEM
BEM01580
C-----------------------------------------------------------------------BEM01590
C
BEM01600
IMPLICIT REAL *8 (A-H,O-Z)
BEM01610
C
BEM01620
PARAMETER (NNODMP=4)
BEM01630
C
BEM01640
INTEGER *2 NADR(NOM),MADR(NOM)
BEM01650
CHARACTER *8 TEXTE(3)
BEM01660
C
BEM01670
DIMENSION X(NOM),Z(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM),VN1(N1), BEM01680
.
VN2(N2),VN3(N3),VN4(N4)
BEM01690
C
BEM01700
COMMON /MAILLE/ NOMM,NELMM,NOM,NELEM,NNODM,N1,N2,N3,N4,I1,I2,
BEM01710
.
I3,I4,ILISS,ISAVE,IO5,IO6,NSAVE
BEM01720
C
BEM01730
DATA EPS /1.D-06/,SOIX/60.D0/,TEXTE/'INPUT 01',
BEM01740
.
'INPUT 02','INPUT 03'/
BEM01750
C
BEM01760
C.....Initialization
BEM01770
C
BEM01780
I1=0
BEM01790
I2=0
BEM01800
I3=0
BEM01810
I4=0
BEM01820
N1=0
BEM01830
N2=0
BEM01840
N3=0
BEM01850
N4=0
BEM01860
C
BEM01870
C.....General data input and check of data
BEM01880
C
BEM01890
READ(IO5,1000,END=200) NOM,NELEM,ILISS,ISAVE,ICOND
BEM01900
C
BEM01910
IF((NOM.GT.NOMM.OR.NOM.LT.0).OR.(NELEM.GT.NELMM.OR.NELEM.LT.0))
BEM01920
.
THEN
BEM01930
CALL ERRORS(TEXTE(1))
BEM01940
C
----------BEM01950
END IF
BEM01960
C
BEM01970
IF((ILISS.NE.0.AND.ILISS.NE.1).OR.(ISAVE.NE.0.AND.ISAVE.NE.1)
BEM01980
.
.OR.(ICOND.NE.0.AND.ICOND.NE.1))THEN
BEM01990
CALL ERRORS(TEXTE(1))
BEM02000
C
----------BEM02010
END IF
BEM02020
C
BEM02030
C.....General title and general data printing
BEM02040
C
BEM02050
WRITE(IO6,2000)
BEM02060
WRITE(IO6,2010) NOM,NELEM,ILISS,ISAVE,ICOND
BEM02070
C
BEM02080
C.....Nodal Coordinates and initial conditions input
BEM02090
C
BEM02100
READ(IO5,1010,END=200)(X(I),Z(I),I=1,NOM)
BEM02110
C
BEM02120
C.....Elements input and checking
BEM02130
C
BEM02140
C
Print title
BEM02150
C
BEM02160
WRITE(IO6,2040)
BEM02170
C
BEM02180
INADR=0
BEM02190
DO IE=1,NELEM
BEM02200
C
BEM02210
READ(IO5,1020,END=200)(MDELEM(I,IE),I=1,NNODMP+4)
BEM02220
C
BEM02230
NSIDE=MDELEM(NNODMP+4,IE)
BEM02240
NNODE=MDELEM(NNODMP+1,IE)
BEM02250
C
BEM02260

.
C

IF((NSIDE.LT.1.OR.NSIDE.GT.4).OR.(NNODE.LT.2.OR.NNODE.GT.4))
THEN
CALL ERRORS(TEXTE(2))
----------END IF

DO I=1,NNODE
IF(MDELEM(I,IE).LE.0.OR.MDELEM(I,IE).GT.NOM) THEN
CALL ERRORS(TEXTE(2))
----------END IF
END DO

C
C
C

Print element IE data


.

WRITE(IO6,2050) IE,NSIDE,MDELEM(NNODMP+2,IE),MDELEM(NNODMP+3,
IE),(MDELEM(I,IE),I=1,NNODE)
IF((DFLOAT(IE+10)/SOIX-DFLOAT((IE+10)/60)).LT.EPS) THEN
WRITE(IO6,2060)
END IF

C
C........Boundary conditions, localisation
C
IINTR=0
DO I=1,NNODE
L=MDELEM(I,IE)
INADR=INADR+1
IINTR=IINTR+1
JLOC=INADR
DO J=1,INADR-1
IF(MADR(J).EQ.L) THEN
JLOC=J
INADR=INADR-1
IINTR=IINTR-1
END IF
END DO
MADR(JLOC)=L
END DO
C
IF(NSIDE.EQ.1) THEN
N1=N1+1
I1=I1+IINTR
ELSE IF(NSIDE.EQ.2) THEN
N2=N2+1
I2=I2+IINTR
ELSE IF(NSIDE.EQ.3) THEN
N3=N3+1
I3=I3+IINTR
ELSE IF(NSIDE.EQ.4) THEN
N4=N4+1
I4=I4+IINTR
END IF
END DO
WRITE(IO6,2070) N1,I1,N2,I2,N3,I3,N4,I4
C
C.....Initializations
C
N1=I1
N2=I2
N3=I3
N4=I4
C
C.....Read boundary conditions
C
DO J=1,N1/8+1
READ(IO5,*,END=200) (VN1(I),I=(J-1)*8+1,MIN(J*8,N1))
END DO
DO J=1,N2/8+1
READ(IO5,*,END=200) (VN2(I),I=(J-1)*8+1,MIN(J*8,N2))
END DO
DO J=1,N3/8+1
READ(IO5,*,END=200) (VN3(I),I=(J-1)*8+1,MIN(J*8,N3))
END DO
DO J=1,N4/8+1
READ(IO5,*,END=200) (VN4(I),I=(J-1)*8+1,MIN(J*8,N4))
END DO

BEM02270
BEM02280
BEM02290
BEM02300
BEM02310
BEM02320
BEM02330
BEM02340
BEM02350
BEM02360
BEM02370
BEM02380
BEM02390
BEM02400
BEM02410
BEM02420
BEM02430
BEM02440
BEM02450
BEM02460
BEM02470
BEM02480
BEM02490
BEM02500
BEM02510
BEM02520
BEM02530
BEM02540
BEM02550
BEM02560
BEM02570
BEM02580
BEM02590
BEM02600
BEM02610
BEM02620
BEM02630
BEM02640
BEM02650
BEM02660
BEM02670
BEM02680
BEM02690
BEM02700
BEM02710
BEM02720
BEM02730
BEM02740
BEM02750
BEM02760
BEM02770
BEM02780
BEM02790
BEM02800
BEM02810
BEM02820
BEM02830
BEM02840
BEM02850
BEM02860
BEM02870
BEM02880
BEM02890
BEM02900
BEM02910
BEM02920
BEM02930
BEM02940
BEM02950
BEM02960
BEM02970
BEM02980
BEM02990
BEM03000
BEM03010

C
BEM03020
C.....Double nodes localisation
BEM03030
C
BEM03040
IDN=0
BEM03050
DO I=1,NOM
BEM03060
XI=X(I)
BEM03070
ZI=Z(I)
BEM03080
LXZI(I)=0
BEM03090
DO J=1,NOM
BEM03100
IF(DABS(XI-X(J)).LT.EPS.AND.DABS(ZI-Z(J)).LT.EPS
BEM03110
.
.AND.I.NE.J) THEN
BEM03120
LXZI(I)=J
BEM03130
IDN=IDN+1
BEM03140
WRITE(IO6,2080) I,J
BEM03150
IF((DFLOAT(17+IDN)/SOIX-DFLOAT((17+IDN)/60)).LT.EPS) THENBEM03160
WRITE(IO6,2060)
BEM03170
END IF
BEM03180
END IF
BEM03190
END DO
BEM03200
END DO
BEM03210
WRITE(IO6,2090) IDN/2
BEM03220
C
BEM03230
RETURN
BEM03240
C
BEM03250
C
End of data
BEM03260
C
BEM03270
200 CALL ERRORS(TEXTE(3))
BEM03280
C
----------BEM03290
C
BEM03300
STOP
BEM03310
C
BEM03320
1000 FORMAT(5I5)
BEM03330
1010 FORMAT(2F10.0)
BEM03340
1020 FORMAT(8I5)
BEM03350
C
BEM03360
2000 FORMAT(1H1,T20,' 2D-BOUNDARY ELEMENT METHOD'/
BEM03370
.
1H ,T20,' =========================='/
BEM03380
.
1H ,T13,'(by S. Grilli, Ocean Engng.,U. of RI (1994))'//
BEM03390
.
1H0,T20,'Discretization and stepping data'/
BEM03400
.
1H ,T20,'===============================')
BEM03410
2010 FORMAT(1H0,T5,'Number of boundary nodes......:',I5/
BEM03420
.
1H0,T5,'Number of boundary elements...:',I5/
BEM03430
.
1H0,T5,'Type of C(i) computation......:',I5/
BEM03440
.
1H0,T5,'Save shape functions..........:',I5/
BEM03450
.
1H0,T5,'Compute condition number......:',I5)
BEM03460
2040 FORMAT(1H1,T10,'Boundary elements data'/
BEM03470
.
1H ,T10,'======================'///
BEM03480
.
1H ,'Element
Boundary Reg.int. Sg. int.
Nodes'/
BEM03490
.
1H ,'-------------- -------- ------------'//) BEM03500
2050 FORMAT(1H ,4(I5,5X),4I5)
BEM03510
2060 FORMAT(1H1)
BEM03520
2070 FORMAT(1H1,T10,'Boundary analysis'/
BEM03530
.
1H ,T10,'================='///
BEM03540
.
1H0,T5,'Number of Boundary 1. elements.....:',I5,
BEM03550
.
T65,'Number of Boundary 1. nodes........:',I5/
BEM03560
.
1H0,T5,'Number of Boundary 2. elements.....:',I5,
BEM03570
.
T65,'Number of Boundary 2. nodes........:',I5/
BEM03580
.
1H0,T5,'Number of Boundary 3. elements.....:',I5,
BEM03590
.
T65,'Number of Boundary 3. nodes........:',I5/
BEM03600
.
1H0,T5,'Number of Boundary 4. elements.....:',I5,
BEM03610
.
T65,'Number of Boundary 4. nodes........:',I5/
BEM03620
.
//1H ,T5,'Double nodes'/
BEM03630
.
1H ,T5,'------------'//)
BEM03640
2080 FORMAT(1H ,T5,2(I5,5X))
BEM03650
2090 FORMAT(1H0,T5,'Number of double nodes....:',I5)
BEM03660
C
BEM03670
END
BEM03680
C-----------------------------------------------------------------------BEM03690
SUBROUTINE BEMK(ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR,
BEM03700
.
MADR)
BEM03710
C-----------------------------------------------------------------------BEM03720
C0 BEMKF
BEMK
BEM03730
C1 PURPOSE
Compute all the Ku and Kq, c (direct or rigid mode: ILISS BEM03740
C1
(0/1)) for the 2D-BEM, and introduce c into Kq
BEM03750
C2 CALL
CALL BEMK(ZKG,ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR, BEM03760
C2
MADR)
BEM03770

C3 CALL ARG. X(NOM),Z(NOM)


= Coordinates of discretization nodes BEM03780
C3
LXZI(NOM)
= Addresses of possible double nodes BEM03790
C3
NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM03800
C3
MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR,
BEM03810
C3
NINTS,NSIDE)
BEM03820
C3
C(NOM)
= Coefficients c incase of dir. comp. BEM03830
C3
ZKQL(NOM,NNODE)
= Local Kq matrix of element IE
BEM03840
C3
ZKUL(NOM,NNODE)
= Local Ku matrix of element IE
BEM03850
C3
XLOC(NNODE)
= X-coordinates of element IE nodes
BEM03860
C3
ZLOC(NNODE)
= Z-coordinates of element IE nodes
BEM03870
C3
NODE(NNODE)
= Nodes of element IE
BEM03880
C3
ZKQG(NOM,NOM)
= Global Kq matrix
BEM03890
C3
ZKUG(NOM,NOM)
= Global Ku matrix
BEM03900
C3
NOM,NELEM
= Discr. nb. of nodes and elements
BEM03910
C3
NOMM
= Discr. max nb. of nodes
BEM03920
C3
NNODM
= Discr. max nb. of nodes per element BEM03930
C3
NINTR,NINTS
= Nb. of regular and singular int. ptsBEM03940
C3
N1,N2,N3,N4
= Nb. of nodes of bound. 1,2,3,4
BEM03950
C3
NSAVE
= Save file number
BEM03960
C4 RET. ARG. ZKUG,ZKQG,NADR,MADR
BEM03970
C6 INT.CALL BIMAT,ASSEML,INTERCI,ANNULU,ANNULD
BEM03980
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM03990
CLBEMK SUB. WHICH COMPUTES THE MATRIX Ku,Kq AND K FOR THE 2D-BEM
BEM04000
C-----------------------------------------------------------------------BEM04010
C
BEM04020
IMPLICIT REAL*8(A-H,O-Z)
BEM04030
C
BEM04040
PARAMETER (NNODMP=4)
BEM04050
C
BEM04060
INTEGER *2 NADR(NOM),MADR(NOM)
BEM04070
C
BEM04080
COMMON /MAILLE/ NOMM,IDUM,NOM,NELEM,NNODM,N1,N2,N3,N4,I1,I2,
BEM04090
.
I3,I4,ILISS,ISAVE,IDU(2),NSAVE
BEM04100
COMMON /DELEM/ XLOC(NNODMP),ZLOC(NNODMP),NODE(NNODMP),NNODE,
BEM04110
.
NINTR,NINTS,NSIDE
BEM04120
C
BEM04130
C.....Procedure vectors and matrices dimensioning
BEM04140
C
BEM04150
C
Domain geometry and topology
BEM04160
C
BEM04170
DIMENSION X(NOM),Z(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM)
BEM04180
C
BEM04190
C
Working matrices
BEM04200
C
BEM04210
DIMENSION ZKUL(NOMM,NNODM),ZKQL(NOMM,NNODM)
BEM04220
C
BEM04230
C
Problem matrices (results of the procedure)
BEM04240
C
BEM04250
DIMENSION ZKUG(NOMM,NOM),ZKQG(NOMM,NOM),C(NOM)
BEM04260
C
BEM04270
C.....Initialize the system matrices, and adressing variables
BEM04280
C
BEM04290
CALL ANNULD(ZKQG,NOMM,NOM,NOM)
BEM04300
C
----------BEM04310
CALL ANNULD(ZKUG,NOMM,NOM,NOM)
BEM04320
C
----------BEM04330
CALL ANNULU(C,NOM)
BEM04340
C
----------BEM04350
C
BEM04360
DO I=1,NOM
BEM04370
NADR(I)=0
BEM04380
END DO
BEM04390
C
BEM04400
I1=0
BEM04410
I2=0
BEM04420
I3=0
BEM04430
I4=0
BEM04440
C
BEM04450
C.....Loop on the elements, local computations, assembling
BEM04460
C
BEM04470
DO IE=1,NELEM
BEM04480
C
BEM04490
C
Local values assigned to element IE
BEM04500
C
BEM04510
NSIDE=MDELEM(NNODMP+4,IE)
BEM04520
NNODE=MDELEM(NNODMP+1,IE)
BEM04530

DO J=1,NNODE
NODE(J)=MDELEM(J,IE)
XLOC(J)=X(NODE(J))
ZLOC(J)=Z(NODE(J))
END DO
NINTR=MDELEM(NNODMP+2,IE)
NINTS=MDELEM(NNODMP+3,IE)

BEM04540
BEM04550
BEM04560
BEM04570
BEM04580
BEM04590
BEM04600
C
BEM04610
C
Computation of local matrices, save geometry and shape funct. BEM04620
C
on file NSAVE
BEM04630
C
BEM04640
CALL BIMAT(ZKQL,ZKUL,C,X,Z,LXZI)
BEM04650
C
---------BEM04660
C
BEM04670
C
Global assembling
BEM04680
C
BEM04690
CALL ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR)
BEM04700
C
----------BEM04710
C
BEM04720
END DO
BEM04730
C
BEM04740
C.....Introduction of C(I) in the system matrices, and inverse assembl. BEM04750
C
BEM04760
CALL INTRCI(ZKQG,C,NADR,MADR)
BEM04770
C
----------BEM04780
C
BEM04790
RETURN
BEM04800
C
BEM04810
END
BEM04820
C-----------------------------------------------------------------------BEM04830
SUBROUTINE BIMAT(ZKQL,ZKUL,C,X,Z,LXZI)
BEM04840
C-----------------------------------------------------------------------BEM04850
C0 BIMATF
BIMAT
BEM04860
C1 PURPOSE
Compute the local Kul and Kql to the elemt IE and c if
BEM04870
C1
direct (ILISS=0) for the 2D-BEM
BEM04880
C2 CALL
CALL BIMAT(ZKQL,ZKUL,C,X,Z,LXZI)
BEM04890
C3 CALL ARG. X(NOM),Z(NOM)
= Coordinates of discretization nodes BEM04900
C3
LXZI(NOM)
= Addresses of possible double nodes BEM04910
C3
C(NOM)
= Coefficients c in case of dir. comp.BEM04920
C3
NOM,NELEM
= Discr. nb. of nodes and elements
BEM04930
C3
NOMM
= Discr. max nb. of nodes
BEM04940
C3
NNODM
= Discr. max nb. of nodes per element BEM04950
C3
NSAVE
= Save file number
BEM04960
C3
ZKQL(NOM,NNODE)
= Local Kq matrix of element IE
BEM04970
C3
ZKUL(NOM,NNODE)
= Local Ku matrix of element IE
BEM04980
C3
NINTR,NINTS
= Nb. of reg. and sing. int. pts of IEBEM04990
C3
SGCI,SGKQ
= Local particular integration on IE BEM05000
C3
IP
= current integration point of IE
BEM05010
C3
NODE(NNODE)
= Nodes of element IE
BEM05020
C3
FI(NNODE)
= Shape functions and
) At point BEM05030
C3
DFI(NNODE),D2FI()
= their derivatives
)
IP
BEM05040
C3
WEIGHT
= current integr. point integr. weightBEM05050
C3
XIP,ZIP
= Current integr. point coordinates
BEM05060
C3
ZNX,ZNZ
= Current integr. point normal vector BEM05070
C3
DS
= Current integr. point jacobian
BEM05080
C4 RET. ARG. ZKUL,ZKQL
BEM05090
C6 INT.CALL FUNC1D,CARAC1,SGDUDN
BEM05100
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM05110
CLBIMAT SUB. WHICH COMPUTES THE MATRIX Kul AND Kql OF IE FOR THE 2D-BEM BEM05120
C-----------------------------------------------------------------------BEM05130
C
BEM05140
IMPLICIT REAL*8(A-H,O-Z)
BEM05150
C
BEM05160
PARAMETER (NNODMP=4)
BEM05170
C
BEM05180
COMMON /MAILLE/ NOMM,IDUM,NOM,IDU(11),ISAVE,IDV(2),NSAVE
BEM05190
COMMON /DELEM/ DUMY(2*NNODMP),NODE(NNODMP),NNODE,NINTR,NINTS,IDW BEM05200
COMMON /FUNCTN/ FI(NNODMP),DFI(NNODMP),D2FI(NNODMP),XIP,ZIP,
BEM05210
.
ZNX,ZNZ,WEIGHT,DS,IP
BEM05220
C
BEM05230
DIMENSION ZKUL(NOMM,NNODE),ZKQL(NOMM,NNODE),C(NOM)
BEM05240
C
BEM05250
DIMENSION X(NOM),Z(NOM),LXZI(NOM)
BEM05260
C
BEM05270
DIMENSION SGCI(NNODMP),SGKQ(NNODMP,NNODMP)
BEM05280
C
BEM05290

.
C
C
C
C
C

DATA ONE/1.D0/,TWO/2.D0/,ZERO/0.D0/,HALF/.5D0/,
PII2/.1591549430918953D0/
Boundary integrals on element IE
Initialisation of local matrices
DO J=1,NNODE
DO I=1,NOM
ZKQL(I,J)=ZERO
ZKUL(I,J)=ZERO
END DO
END DO

C
C
C

Regular integration

DO IP=1,NINTR
CALL FUNC1D(0,0,ETA)
----------CALL CARAC1
-----------

C
C
C
C

Save geometry and shape functions on file NSAVE

.
C
C
C

IF(ISAVE.EQ.1) THEN
WRITE(NSAVE) ETA,XIP,ZIP,(FI(I),DFI(I),D2FI(I),I=1,NNODE),
DS,WEIGHT,ZNX,ZNZ
END IF
Computation of ZKUL, ZKQL
DS=DS*WEIGHT
DO I=1,NOM
XX=XIP-X(I)
ZZ=ZIP-Z(I)
R=DSQRT(XX*XX+ZZ*ZZ)

C
C
C

Computation of Green functions


DUDN=-PII2*(ZNX*XX+ZNZ*ZZ)/(R*R)
U=DLOG(R)

C
C
C

Kernel transformation, in case of I on IE


DO J=1,NNODE
IF (I.EQ.NODE(J)) THEN
ETAI=(TWO*J-NNODE-ONE)/(NNODE-ONE)
ETAP=DABS(ETA-ETAI)*HALF
U=U-DLOG(ETAP)
DUDN=ZERO
END IF
END DO
U=-U*PII2

C
C(I)=C(I)-DUDN*DS
DO J=1,NNODE
ZKUL(I,J)=ZKUL(I,J)+FI(J)*U*DS
ZKQL(I,J)=ZKQL(I,J)+FI(J)*DUDN*DS
END DO
END DO
END DO
C
C
C

Singular integrals for ZKUL


DO I=1,NNODE
M=NODE(I)

C
C
C
C

Second regular part of the singular integrals, and


Singular part of the singular integrals
DO IP=1,NINTS
DO NSG=1,2
DO K=1,2
NSGC=NSG*(2*K-3)
CALL FUNC1D(NSGC,I,ETA)
-----------

BEM05300
BEM05310
BEM05320
BEM05330
BEM05340
BEM05350
BEM05360
BEM05370
BEM05380
BEM05390
BEM05400
BEM05410
BEM05420
BEM05430
BEM05440
BEM05450
BEM05460
BEM05470
BEM05480
BEM05490
BEM05500
BEM05510
BEM05520
BEM05530
BEM05540
BEM05550
BEM05560
BEM05570
BEM05580
BEM05590
BEM05600
BEM05610
BEM05620
BEM05630
BEM05640
BEM05650
BEM05660
BEM05670
BEM05680
BEM05690
BEM05700
BEM05710
BEM05720
BEM05730
BEM05740
BEM05750
BEM05760
BEM05770
BEM05780
BEM05790
BEM05800
BEM05810
BEM05820
BEM05830
BEM05840
BEM05850
BEM05860
BEM05870
BEM05880
BEM05890
BEM05900
BEM05910
BEM05920
BEM05930
BEM05940
BEM05950
BEM05960
BEM05970
BEM05980
BEM05990
BEM06000
BEM06010
BEM06020
BEM06030
BEM06040
BEM06050

BEM06060
BEM06070
BEM06080
BEM06090
BEM06100
BEM06110
BEM06120
BEM06130
BEM06140
BEM06150
C
BEM06160
C
Particular Integral for ZKQL, C (NNODE > 2)
BEM06170
C
BEM06180
IF(NNODE.GT.2) THEN
BEM06190
CALL SGDUDN(SGKQ,SGCI)
BEM06200
C
----------BEM06210
DO I=1,NNODE
BEM06220
M=NODE(I)
BEM06230
C(M)=C(M)+SGCI(I)
BEM06240
DO J=1,NNODE
BEM06250
ZKQL(M,J)=ZKQL(M,J)+SGKQ(I,J)
BEM06260
END DO
BEM06270
END DO
BEM06280
END IF
BEM06290
C
BEM06300
C
Double nodes, taking into account for the sing. and part. integ. BEM06310
C
BEM06320
DO I=1,NNODE
BEM06330
M=NODE(I)
BEM06340
IF(LXZI(M).NE.0) THEN
BEM06350
DO J=1,NNODE
BEM06360
ZKUL(LXZI(M),J)=ZKUL(M,J)
BEM06370
ZKQL(LXZI(M),J)=ZKQL(M,J)
BEM06380
END DO
BEM06390
END IF
BEM06400
END DO
BEM06410
C
BEM06420
RETURN
BEM06430
C
BEM06440
END
BEM06450
C---------------------------------------------------------------------- BEM06460
SUBROUTINE ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR)
BEM06470
C---------------------------------------------------------------------- BEM06480
C0 ASSEMLF
ASSEML
BEM06490
C1 PURPOSE
Assemble local Kul and Kql of the elemt IE in the global BEM06500
C1
matrix Ku and Kq for the 2D-BEM(in order N1,N2,N3,N4),
BEM06510
C1
and set NADR
BEM06520
C2 CALL
CALL ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR)
BEM06530
C3 CALL ARG. NOM
= Discr. nb. of nodes
BEM06540
C3
NOMM
= Discr. max nb. of nodes
BEM06550
C3
N1,N2,N3,N4
= Nb. of nodes of bound. 1,2,3,4
BEM06560
C3
ZKQG(NOM,NOM)
= Global Kq matrix
BEM06570
C3
ZKUG(NOM,NOM)
= Global Ku matrix
BEM06580
C3
ZKQL(NOM,NNODE)
= Local Kq matrix of element IE
BEM06590
C3
ZKUL(NOM,NNODE)
= Local Ku matrix of element IE
BEM06600
C3
NODE(NNODE)
= Nodes of element IE
BEM06610
C4 RET. ARG. ZKUG,ZKQG,NADR
BEM06620
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM06630
CLASSEML SUB. WHICH ASSEMBLES MATRIX Kul AND Kql OF IE FOR THE 2D-BEM
BEM06640
C-----------------------------------------------------------------------BEM06650
C
BEM06660
IMPLICIT REAL*8(A-H,O-Z)
BEM06670
C
BEM06680
PARAMETER (NNODMP=4)
BEM06690
C
BEM06700
INTEGER *2 NADR(NOM)
BEM06710
C
BEM06720
COMMON /MAILLE/ NOMM,IDVM,NOM,IDU(2),N1,N2,N3,N4,I1,I2,I3,I4,IV(5)BEM06730
COMMON /DELEM/ DUM1(2*NNODMP),NODE(NNODMP),NNODE,IDUM(2),NSIDE
BEM06740
C
BEM06750
DIMENSION ZKQG(NOMM,NOM),ZKUG(NOMM,NOM),ZKQL(NOMM,NNODE),
BEM06760
.
ZKUL(NOMM,NNODE)
BEM06770
C
BEM06780
DATA ONE/1.D0/,HALF/.5D0/
BEM06790
C
BEM06800
DO J=1,NNODE
BEM06810
C

CALL CARAC1
----------DS=DS*WEIGHT
DO J=1,NNODE
ZKUL(M,J)=ZKUL(M,J)-FI(J)*DS*PII2
END DO
END DO
END DO
END DO
END DO

K=NODE(J)

BEM06820

C
IF(NSIDE.EQ.1) THEN
C
C...........Boundary NSIDE=1
C
I1P=I1
I1=I1+1
KLOC=I1
DO L=1,I1P
IF(NADR(L).EQ.K) THEN
KLOC=L
I1=I1-1
END IF
END DO
NADR(KLOC)=K
DO I=1,NOM
ZKUG(I,KLOC)=ZKUG(I,KLOC)+ZKUL(I,J)
ZKQG(I,KLOC)=ZKQG(I,KLOC)+ZKQL(I,J)
END DO
ELSE IF(NSIDE.EQ.2) THEN
C
C...........Boundary NSIDE=2
C
I2P=I2
I2=I2+1
KLOC=I2
DO L=1,I2P
IF(NADR(L+N1).EQ.K) THEN
KLOC=L
I2=I2-1
END IF
END DO
NADR(KLOC+N1)=K
DO I=1,NOM
ZKUG(I,KLOC+N1)=ZKUG(I,KLOC+N1)+ZKUL(I,J)
ZKQG(I,KLOC+N1)=ZKQG(I,KLOC+N1)+ZKQL(I,J)
END DO
ELSE IF(NSIDE.EQ.3) THEN
C
C...........Boundary NSIDE=3
C
I3P=I3
I3=I3+1
KLOC=I3
NC=N1+N2
DO L=1,I3P
IF(NADR(L+NC).EQ.K) THEN
KLOC=L
I3=I3-1
END IF
END DO
NADR(KLOC+NC)=K
DO I=1,NOM
ZKUG(I,KLOC+NC)=ZKUG(I,KLOC+NC)+ZKUL(I,J)
ZKQG(I,KLOC+NC)=ZKQG(I,KLOC+NC)+ZKQL(I,J)
END DO
ELSE IF(NSIDE.EQ.4) THEN
C
C...........Boundary NSIDE=4
C
I4P=I4
I4=I4+1
KLOC=I4
NC=N1+N2+N3
DO L=1,I4P
IF(NADR(L+NC).EQ.K) THEN
KLOC=L
I4=I4-1
END IF
END DO
NADR(KLOC+NC)=K
DO I=1,NOM
ZKUG(I,KLOC+NC)=ZKUG(I,KLOC+NC)+ZKUL(I,J)
ZKQG(I,KLOC+NC)=ZKQG(I,KLOC+NC)+ZKQL(I,J)
END DO

10

BEM06830
BEM06840
BEM06850
BEM06860
BEM06870
BEM06880
BEM06890
BEM06900
BEM06910
BEM06920
BEM06930
BEM06940
BEM06950
BEM06960
BEM06970
BEM06980
BEM06990
BEM07000
BEM07010
BEM07020
BEM07030
BEM07040
BEM07050
BEM07060
BEM07070
BEM07080
BEM07090
BEM07100
BEM07110
BEM07120
BEM07130
BEM07140
BEM07150
BEM07160
BEM07170
BEM07180
BEM07190
BEM07200
BEM07210
BEM07220
BEM07230
BEM07240
BEM07250
BEM07260
BEM07270
BEM07280
BEM07290
BEM07300
BEM07310
BEM07320
BEM07330
BEM07340
BEM07350
BEM07360
BEM07370
BEM07380
BEM07390
BEM07400
BEM07410
BEM07420
BEM07430
BEM07440
BEM07450
BEM07460
BEM07470
BEM07480
BEM07490
BEM07500
BEM07510
BEM07520
BEM07530
BEM07540
BEM07550
BEM07560

END IF
END DO

BEM07570
BEM07580
RETURN
BEM07590
C
BEM07600
END
BEM07610
C---------------------------------------------------------------------- BEM07620
SUBROUTINE INTRCI(ZKQG,C,NADR,MADR)
BEM07630
C---------------------------------------------------------------------- BEM07640
C0 INTRCIF
INTRCI
BEM07650
C1 PURPOSE
Introduce c coefficients into Kq either from their direct BEM07660
C1
knowledge (ILISS=0) or by the "rigid mode" method (=1).
BEM07670
C1
Set inverse adressing vector MADR
BEM07680
C2 CALL
CALL INTRCI(ZKQG,C,NADR,MADR)
BEM07690
C3 CALL ARG. NOM
= Discr. nb. of nodes
BEM07700
C3
NOMM
= Discr. max nb. of nodes
BEM07710
C3
ILISS
= Mode of C computation (0/1)
BEM07720
C3
C(NOM)
= Coefficients c incase of dir. comp. BEM07730
C3
ZKQG(NOM,NOM)
= Global Kq matrix of element IE
BEM07740
C3
NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM07750
C4 RET. ARG. ZKQG,MADR
BEM07760
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM07770
CLINTRCI SUB. WHICH INTRODUCES C INTO Kq FOR THE 2D-BEM
BEM07780
C-----------------------------------------------------------------------BEM07790
C
BEM07800
IMPLICIT REAL*8(A-H,O-Z)
BEM07810
C
BEM07820
INTEGER *2 NADR(NOM),MADR(NOM)
BEM07830
C
BEM07840
COMMON /MAILLE/ NOMM,IDUM,NOM,IDU(10),ILISS,IDV(4)
BEM07850
C
BEM07860
DIMENSION ZKQG(NOMM,NOM),C(NOM)
BEM07870
C
BEM07880
DATA ZERO/0.D0/
BEM07890
C
BEM07900
C
Set inverse adressing vector
BEM07910
C
BEM07920
DO I=1,NOM
BEM07930
MADR(NADR(I))=I
BEM07940
END DO
BEM07950
C
BEM07960
DO I=1,NOM
BEM07970
L=NADR(I)
BEM07980
IF(ILISS.EQ.0) THEN
BEM07990
C
BEM08000
C
Direct C(I)
BEM08010
C
BEM08020
ZKQG(L,I)=ZKQG(L,I)+C(L)
BEM08030
ELSE
BEM08040
C
BEM08050
C
C(I) by the rigid mode technique
BEM08060
C
BEM08070
ZKQG(L,I)=ZERO
BEM08080
DO J=1,NOM
BEM08090
IF(I.NE.J) THEN
BEM08100
ZKQG(L,I)=ZKQG(L,I)-ZKQG(L,J)
BEM08110
END IF
BEM08120
END DO
BEM08130
END IF
BEM08140
END DO
BEM08150
C
BEM08160
RETURN
BEM08170
C
BEM08180
END
BEM08190
C-----------------------------------------------------------------------BEM08200
SUBROUTINE FUNC1D (NSG,IN,ETA)
BEM08210
C-----------------------------------------------------------------------BEM08220
C0 FUNC1DF
FUNC1D
BEM08230
C1 PURPOSE
Compute interpolation functions for 1D-isoparametric
BEM08240
C1
elements, and their derivatives at integ. point IP
BEM08250
C2 CALL
CALL FUNC1D(NSG,IN,ETA)
BEM08260
C3 CALL ARG. NNODE
= Number of nodes of the element
BEM08270
C3
NINTR,NINTS
= Number of reg. or sing. int. points BEM08280
C3
IP
= Indice of current integration point BEM08290
C3
NSG=0
= Regular GAUSS quadrature
BEM08300
C3
NSG<0
= GAUSS quadr. on 2d regular terms
BEM08310
C

11

C3
NSG>0
= BERTHOD-ZABOROWISKY sing. integr.
BEM08320
C4 RET. ARG. FI(NNODE),ETA
= Shape functions and
) At point BEM08330
C4
DFI(NNODE),D2FI()
= their derivatives
)
IP
BEM08340
C4
WEIGHT
= Integration weight
BEM08350
C6 INT.CALL FUNF1,DFUNF1,D2FUN1,ERRORS
BEM08360
CE ERRORS
01= Incorrect number of integration points (2 To 6).
BEM08370
CE
02= Incorrect number of elements nodes (2 to NDM)
BEM08380
CE
03= Indice of integration point out of order
BEM08390
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM08400
CLFUNC1D SUB. COMP. OF INTERP FUNCTION FOR 1-DIM ISOPAR. ELETS
BEM08410
C-----------------------------------------------------------------------BEM08420
C
BEM08430
IMPLICIT REAL*8 (A-H,O-Z)
BEM08440
C
BEM08450
PARAMETER (NNODMP=4)
BEM08460
C
BEM08470
CHARACTER *8 TEXTE1,TEXTE2,TEXTE3
BEM08480
C
BEM08490
DIMENSION XIP(5,3),WIP(5,3),XIS(6,5),WIS(6,5)
BEM08500
C
BEM08510
COMMON /FUNCTN/ FI(NNODMP),DFI(NNODMP),D2FI(NNODMP),DUM(4),
BEM08520
.
WEIGHT,DS,IP
BEM08530
COMMON /DELEM/ DUMY(2*NNODMP),IDV(NNODMP),NNODE,NINTR,NINTS,IDUM BEM08540
C
BEM08550
DATA TEXTE1/'FUNC1D01'/,TEXTE2/'FUNC1D02'/,TEXTE3/'FUNC1D03'/,
BEM08560
.
ONE/1.D0/,TWO/2.D0/,THREE/3.D0/,HALF/0.5D0/,
BEM08570
.
EPS/1.D-08/,ZERO/0.D0/
BEM08580
DATA XIP/.577350269189626D0,0.D0,.339981043584856D0,
BEM08590
.
.538469310105683D0,.238619186083197D0,0.D0,
BEM08600
.
.774596669241483D0,.861136311594053D0,.906179845938664D0,BEM08610
.
.661209386466265D0,4*0.D0,.932469514203152D0/
BEM08620
DATA WIP/1.D0,.888888888888889D0,.652145154862546D0,
BEM08630
.
.478628670499366D0,.467913934572691D0,0.D0,
BEM08640
.
.555555555555556D0,.347854845137454D0,.236926885056189D0,BEM08650
.
.360761573048139D0,3*0.D0,.568888888888889D0,
BEM08660
.
.171324492379170D0/
BEM08670
DATA XIS/.112008806166976D0 ,.602276908118738D0,4*0.D0,
BEM08680
.
.638907930873254D-01,.368997063715619D0,
BEM08690
.
.766880303938941D0 ,3*0.D0,
BEM08700
.
.414484801993832D-01,.245274914320602D0,
BEM08710
.
.556165453560276D0 ,.848982394532985D0,2*0.D0,
BEM08720
.
.291344721519721D-01,.173977213320898D0,
BEM08730
.
.411702520284902D0 ,.677314174582820D0,
BEM08740
.
.894771361031008D0 ,0.D0,
BEM08750
.
.216340058441169D-01,.129583391154951D0,
BEM08760
.
.314020449914766D0 ,.538657217351802D0,
BEM08770
.
.756915337377403D0 ,.922668851372120D0/
BEM08780
DATA WIS/.718539319030384D0 ,.281460680969616D0,4*0.D0,
BEM08790
.
.513404552232363D0 ,.391980041201488D0,
BEM08800
.
.946154065661491D-01,3*0.D0,
BEM08810
.
.383464068145135D0 ,.386875317774763D0,
BEM08820
.
.190435126950142D0 ,.392254871299598D-01,2*0.D0,
BEM08830
.
.297893471782894D0 ,.349776226513224D0,
BEM08840
.
.234488290044052D0 ,.989304595166331D-01,
BEM08850
.
.189115521431958D-01,0.D0,
BEM08860
.
.238763662578548D0 ,.308286573273947D0,
BEM08870
.
.245317426563210D0 ,.142008756566477D0,
BEM08880
.
.554546223248863D-01,.101689586929323D-01/
BEM08890
C
BEM08900
IF (NNODE.LT.2.OR.NNODE.GT.4) CALL ERRORS (TEXTE2)
BEM08910
C
----------BEM08920
NINT=NINTR
BEM08930
IF (NSG.NE.0) NINT=NINTS
BEM08940
IF (NINT.LT.2.OR.NINT.GT.6) CALL ERRORS (TEXTE1)
BEM08950
C
----------BEM08960
IF (IP.LT.1.OR.IP.GT.NINT) CALL ERRORS (TEXTE3)
BEM08970
C
----------BEM08980
C
BEM08990
IF(NSG.LE.0) THEN
BEM09000
C
BEM09010
C
Gauss quadrature, degree 3 to 11 (2 to 6 nodes)(NSG<=0)
BEM09020
C
BEM09030
IF(NINT.EQ.2) THEN
BEM09040
C
BEM09050
C...........2 integration points
BEM09060
K = 2*IP - 3
BEM09070

12

M = 1
ELSE IF(NINT.EQ.3) THEN
C...........3 integration points
K = IP - 2
M = 5 + IP * (IP-4)
ELSE IF(NINT.EQ.4) THEN
C...........4 integration points
K = 5 + IP * ( IP * (15 - 2*IP) - 31 ) / 3
M = 4 + IP * (IP-5) / 2
ELSE IF(NINT.EQ.5) THEN
C...........5 integration points
K = 1 + IP * ((9-IP) * IP - 20) / 6
M = 27 + IP * ( IP * (347 + IP * (7*IP-84)) - 570 ) /12
ELSE IF(NINT.EQ.6) THEN
C...........6 integration points
K = -21 + IP * (2614 + IP * (IP * (680+IP*(6*IP-105))
.
- 1995))/60
M = 2 + IP * (70 + IP * ( IP * (14-IP) - 59 )) / 24
END IF
C
ETA
= K * XIP(NINT-1,M)
WEIGHT = WIP(NINT-1,M)
ELSE
C
C
Berthod-Zaborwiski quad.,deg. 3 to 11 (2 to 6 nodes)(NSG>0)
C
ETA
=XIS(IP,NINT-1)
WEIGHT=WIS(IP,NINT-1)
END IF
C
C
Modification of ETA, in case of singular integration
C
IF (NSG.NE.0) THEN
ETAI=(TWO*IN-NNODE-ONE)/(NNODE-ONE)
EP=(ONE+THREE*ETAI-TWO*ETAI*IABS(NSG))*HALF
EPSI=TWO*IABS(NSG)-THREE
IF (NSG.LT.0) THEN
C
C
Second regular integration
C
ETA=((ONE-EPSI*ETAI)*ETA+EPSI*(ONE+EPSI*ETAI))*HALF
IF (EP.LT.EPS) THEN
WEIGHT=ZERO
ELSE
WEIGHT=WEIGHT*EP*DLOG(EP)
END IF
ELSE
C
C
Singular integration
C
ETA=ETAI+EPSI*TWO*EP*ETA
WEIGHT=-WEIGHT*TWO*EP
END IF
END IF
C
C
Shape functions and their derivatives
C
CALL FUNF1(ETA)
C
---------CALL DFUNF1(ETA)
C
----------CALL D2FUN1(ETA)
C
----------C
RETURN
C
END
C--------------------------------------------------------------------SUBROUTINE CARAC1
C--------------------------------------------------------------------C0 CARAC1F
CARAC1
C1 PURPOSE
Compute the Xip,Zip,Znx,Znz and Ds at the integration
C1
point IP of the element IE
C2 CALL
CALL CARAC1
C3 CALL ARG. NODE(NNODE)
= Nodes of element IE
C3
XLOC(NNODE)
= X-coordinates of element IE nodes

13

BEM09080
BEM09090
BEM09100
BEM09110
BEM09120
BEM09130
BEM09140
BEM09150
BEM09160
BEM09170
BEM09180
BEM09190
BEM09200
BEM09210
BEM09220
BEM09230
BEM09240
BEM09250
BEM09260
BEM09270
BEM09280
BEM09290
BEM09300
BEM09310
BEM09320
BEM09330
BEM09340
BEM09350
BEM09360
BEM09370
BEM09380
BEM09390
BEM09400
BEM09410
BEM09420
BEM09430
BEM09440
BEM09450
BEM09460
BEM09470
BEM09480
BEM09490
BEM09500
BEM09510
BEM09520
BEM09530
BEM09540
BEM09550
BEM09560
BEM09570
BEM09580
BEM09590
BEM09600
BEM09610
BEM09620
BEM09630
BEM09640
BEM09650
BEM09660
BEM09670
BEM09680
BEM09690
BEM09700
BEM09710
BEM09720
BEM09730
BEM09740
BEM09750
BEM09760
BEM09770
BEM09780
BEM09790
BEM09800

C3
ZLOC(NNODE)
= Z-coordinates of element IE nodes
BEM09810
C3
FI(NNODE)
= Shape functions and
) At point BEM09820
C3
DFI(NNODE),D2FI()
= their derivatives
)
IP
BEM09830
C3
XIP,ZIP
= Current integr. point coordinates
BEM09840
C3
ZNX,ZNZ
= Current integr. point normal vector BEM09850
C3
DS
= Current integr. point jacobian
BEM09860
C4 RET. ARG. XIP,ZIP,DS,ZNX,ZNZ
BEM09870
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM09880
CLCARAC1 SUB. WHICH COMPUTES CARACTERISTICS AT IP OF IE FOR THE 2D-BEM BEM09890
C-----------------------------------------------------------------------BEM09900
C
BEM09910
IMPLICIT REAL*8(A-H,O-Z)
BEM09920
C
BEM09930
PARAMETER (NNODMP=4)
BEM09940
C
BEM09950
COMMON /DELEM/ XLOC(NNODMP),ZLOC(NNODMP),IDUM(NNODMP),NNODE,IDU(3)BEM09960
COMMON /FUNCTN/ FI(NNODMP),DFI(NNODMP),DUM(NNODMP),XIP,ZIP,
BEM09970
.
ZNX,ZNZ,WEIGHT,DS,IP
BEM09980
C
BEM09990
DATA ZERO/0.D0/
BEM10000
C
BEM10010
DXETA=ZERO
BEM10020
DZETA=ZERO
BEM10030
XIP=ZERO
BEM10040
ZIP=ZERO
BEM10050
DO I=1,NNODE
BEM10060
DXETA=DXETA+DFI(I)*XLOC(I)
BEM10070
DZETA=DZETA+DFI(I)*ZLOC(I)
BEM10080
XIP=XIP+FI(I)*XLOC(I)
BEM10090
ZIP=ZIP+FI(I)*ZLOC(I)
BEM10100
END DO
BEM10110
DS=DSQRT(DXETA*DXETA+DZETA*DZETA)
BEM10120
C
BEM10130
C
Dextrorsum Boundary OXZ for the outwards normal vector
BEM10140
C
BEM10150
ZNX=-DZETA/DS
BEM10160
ZNZ= DXETA/DS
BEM10170
C
BEM10180
C
Will serve later, to compute pressure forces
BEM10190
C
BEM10200
C
COSDS(1)=DXETA
BEM10210
C
COSDS(2)=DZETA
BEM10220
C
COSDS(3)=DXETA*XIP-DZETA*ZIP
BEM10230
C
BEM10240
RETURN
BEM10250
C
BEM10260
END
BEM10270
C-----------------------------------------------------------------------BEM10280
SUBROUTINE SGDUDN (ZINT,CINT)
BEM10290
C-----------------------------------------------------------------------BEM10300
C0 SGDUDNF
SGDUDN
BEM10310
C1 PURPOSE
Compute the local particular integration over IE, for
BEM10320
C1
du*/dn for the 2D-BEM(0 if straight-line element)
BEM10330
C2 CALL
CALL SGDUDN(ZINT,CINT)
BEM10340
C3 CALL ARG. NINTR
= Nb. of reg. int. pts of IE
BEM10350
C3
ZINT(,),CINT(NNODE) = Local particular integrals on IE
BEM10360
C3
IP
= current integration point of IE
BEM10370
C3
XLOC(NNODE)
= X-coordinates of element IE nodes
BEM10380
C3
ZLOC(NNODE)
= Z-coordinates of element IE nodes
BEM10390
C3
FI(NNODE)
= Shape functions and
) At point BEM10400
C3
DFI(NNODE)
= their derivatives
)
IP
BEM10410
C3
WEIGHT
= current integr. point integr. weightBEM10420
C3
DS
= Current integr. point jacobian
BEM10430
C4 RET. ARG. ZINT,CINT
BEM10440
C6 INT.CALL FUNC1D,ATANV
BEM10450
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM10460
CLSGDUDN SUB. WHICH COMPUTES THE PARTICULAR INTEG. OF IE FOR THE 2D-BEM BEM10470
C-----------------------------------------------------------------------BEM10480
C
BEM10490
IMPLICIT REAL*8 (A-H,O-Z)
BEM10500
C
BEM10510
PARAMETER (NNODMP=4)
BEM10520
C
BEM10530
DIMENSION ZINT(NNODMP,NNODMP),CINT(NNODMP)
BEM10540
COMMON /DELEM/ XLOC(NNODMP),ZLOC(NNODMP),IDUM(NNODMP),
BEM10550
.
NNODE,NINTR,IDUM1,NSIDE
BEM10560

14

COMMON /FUNCTN/ FI(NNODMP),DFI(NNODMP),DUM(NNODMP+4),


WEIGHT,DS,IP

DO I=1,NNODE
CINT(I)=CINT(I)*CM*PII2*NFINT
DO J=1,NNODE
ZINT(I,J)=ZINT(I,J)*CM*PII2*NFINT
END DO
END DO

BEM10570
BEM10580
BEM10590
BEM10600
BEM10610
BEM10620
BEM10630
BEM10640
BEM10650
BEM10660
BEM10670
BEM10680
BEM10690
BEM10700
BEM10710
BEM10720
BEM10730
BEM10740
BEM10750
BEM10760
BEM10770
BEM10780
BEM10790
BEM10800
BEM10810
BEM10820
BEM10830
BEM10840
BEM10850
BEM10860
BEM10870
BEM10880
BEM10890
BEM10900
BEM10910
BEM10920
BEM10930
BEM10940
BEM10950
BEM10960
BEM10970
BEM10980
BEM10990
BEM11000
BEM11010
BEM11020
BEM11030
BEM11040
BEM11050
BEM11060
BEM11070
BEM11080
BEM11090
BEM11100
BEM11110
BEM11120
BEM11130
BEM11140
BEM11150
BEM11160
BEM11170
BEM11180
BEM11190
BEM11200
BEM11210
BEM11220
BEM11230
BEM11240
BEM11250

DATA ZERO/0.D0/,EPS/1.D-06/,ONE/1.D0/,
PII2/.1591549430918953D0/

RETURN

BEM11260

C
C
C
C

Check if nodes are on line


A1=ZLOC(1)-ZLOC(NNODE)
B1=XLOC(NNODE)-XLOC(1)
C1=XLOC(1)*ZLOC(NNODE)-ZLOC(1)*XLOC(NNODE)
M=0
DO I=2,NNODE-1
X1=A1*XLOC(I)+B1*ZLOC(I)+C1
IF (DABS(X1).GT.EPS) M=1
END DO
IF (M.EQ.0) THEN
CM=ZERO
ELSE

C
C
C

Check if element steepness is > < 45 degrees


IF (DABS(B1).GE.EPS) THEN
CFAG=DABS(A1/B1)
IF (CFAG.LE.ONE) THEN
NFINT=1
END IF
ELSE
NFINT=-1
END IF

C
C
C

Integration
DO I=1,NNODE
XI=XLOC(I)
ZI=ZLOC(I)

C
C
C

Constant part
ZINT(I,1)=-ATANV (XI,ZI,-ONE,NFINT)
----DO K=2,NNODE-1
ZINT(I,K)=ZERO
END DO
ZINT(I,NNODE)=ATANV (XI,ZI,ONE,NFINT)
----CINT(I)=ZINT(I,1)-ZINT(I,NNODE)

C
C
C
C
C
C

Integral part
DO IP=1,NINTR
CALL FUNC1D (0,0,ETA)
----------AV=ATANV(XI,ZI,ETA,NFINT)
----DO J=1,NNODE
ZINT(I,J)=ZINT(I,J)-WEIGHT*DFI(J)*AV
END DO
END DO
END DO
CM=ONE
END IF

C
C
END
BEM11270
C-----------------------------------------------------------------------BEM11280
FUNCTION ATANV (XI,ZI,ETA,NFINT)
BEM11290
C-----------------------------------------------------------------------BEM11300

15

C0 ATANVF
ATANV
BEM11310
C1 PURPOSE
In the local particular integration over IE, for
BEM11320
C1
du/dn, function which returns an arctg whose
BEM11330
C1
value depends on the element position, in the
BEM11340
C1
cartesian coord. axis (OXZ) :
BEM11350
C1
"Vertical " element :
NFINT=-1 => ATANV=ARCTG(X/Z)
BEM11360
C1
"Horizont." element :
NFINT=+1 => ATANV=ARCTG(Z/X)
BEM11370
C1
If the arctg produces an indeterminate form (0/0), the
BEM11380
C1
l'Hospital theorem is applied up to 2 times
BEM11390
C2 CALL
ATANV(XI,ZI,ETA,NFINT)
BEM11400
C3 CALL ARG. XI,ZI
= Coord. of the source point on IE
BEM11410
C3
NFINT
= Position of the element
BEM11420
C3
ETA
= Intrinsic coordinate of IP
BEM11430
C3
IP
= current integration point of IE
BEM11440
C3
NNODE
= Number of nodes of IE
BEM11450
C3
XLOC(NNODE)
= X-coordinates of element IE nodes
BEM11460
C3
ZLOC(NNODE)
= Z-coordinates of element IE nodes
BEM11470
C4 RET. ARG FI(NNODE)
= Shape functions and
) At point BEM11480
C4
DFI(NNODE)
= their 1st derivatives
)
IP
BEM11490
C4
D2FI(NNODE)
= their 2nd derivatives
)
BEM11500
C4
ATANV
BEM11510
C6 INT.CALL ATANS,FUNF1,DFUNF1,D2FUNF1,ERRORS
BEM11520
CE ERRORS
01= The indeterminate form persits
BEM11530
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM11540
CLATANV SUB. WHICH COMPUTES THE ARCTG FOR PAR. INTEG OF IE FOR THE 2D-BEBEM11550
C-----------------------------------------------------------------------BEM11560
C
BEM11570
IMPLICIT REAL*8 (A-H,O-Z)
BEM11580
C
BEM11590
PARAMETER (NNODMP=4)
BEM11600
C
BEM11610
CHARACTER *8 TEXTE
BEM11620
C
BEM11630
COMMON /DELEM/ XLOC(NNODMP),ZLOC(NNODMP),IDUM(NNODMP),
BEM11640
.
NNODE,IDUM1(3)
BEM11650
COMMON /FUNCTN/ FI(NNODMP),DFI(NNODMP),D2FI(NNODMP),DUM(6),IP
BEM11660
C
BEM11670
DATA ZERO/0.D0/,TEXTE/'ATANV 01'/
BEM11680
C
BEM11690
CALL FUNF1 (ETA)
BEM11700
C
---------BEM11710
X=-XI
BEM11720
Z=-ZI
BEM11730
DO I=1,NNODE
BEM11740
X=X+FI(I)*XLOC(I)
BEM11750
Z=Z+FI(I)*ZLOC(I)
BEM11760
END DO
BEM11770
ATANV=ATANS(X,Z,NFINT,NR)
BEM11780
C
----BEM11790
IF(NR.EQ.1) RETURN
BEM11800
CALL DFUNF1 (ETA)
BEM11810
C
----------BEM11820
X=ZERO
BEM11830
Z=ZERO
BEM11840
DO I=1,NNODE
BEM11850
X=X+DFI(I)*XLOC(I)
BEM11860
Z=Z+DFI(I)*ZLOC(I)
BEM11870
END DO
BEM11880
ATANV=ATANS(X,Z,NFINT,NR)
BEM11890
C
----BEM11900
IF(NR.EQ.1) RETURN
BEM11910
CALL D2FUN1 (ETA)
BEM11920
C
----------BEM11930
X=ZERO
BEM11940
Z=ZERO
BEM11950
DO I=1,NNODE
BEM11960
X=X+D2FI(I)*XLOC(I)
BEM11970
Z=Z+D2FI(I)*ZLOC(I)
BEM11980
END DO
BEM11990
ATANV=ATANS(X,Z,NFINT,NR)
BEM12000
C
----BEM12010
IF(NR.EQ.1) RETURN
BEM12020
CALL ERRORS(TEXTE)
BEM12030
C
----------BEM12040
END
BEM12050
C--------------------------------------------------------------------- BEM12060

16

FUNCTION ATANS(X,Z,NFINT,NR)
BEM12070
C--------------------------------------------------------------------- BEM12080
C0 ATANSF
ATANS
BEM12090
C1 PURPOSE
In the local particular integration over IE, for
BEM12100
C1
du*/dn,function which returns an arctg for ATANV and testsBEM12110
C1
if the arctg produces an indeterminate form (0/0) (NR=0) BEM12120
C2 CALL
ATANS(X,Z,ETA,NFINT)
BEM12130
C3 CALL ARG. X,Z
= Coord. of the integr. point on IE
BEM12140
C3
NFINT
= Position of the element (-1,+1)
BEM12150
C4 RET. ARG NR
= Indice of indeterminate form(0/1)
BEM12160
C4
ATANS
BEM12170
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM12180
CLATANS SUB. WHICH COMPUTES THE ARCTG IN PAR. INTEG. OF IE FOR THE 2D-BEBEM12190
C-----------------------------------------------------------------------BEM12200
C
BEM12210
IMPLICIT REAL *8 (A-H,O-Z)
BEM12220
DATA EPS/1.D-06/,PID2/1.5707963267949D0/
BEM12230
C
BEM12240
IF ((DABS(X).GE.EPS).OR.(DABS(Z).GE.EPS)) THEN
BEM12250
C
BEM12260
C
Return true
BEM12270
C
BEM12280
IF (NFINT.EQ.1) THEN
BEM12290
IF (DABS(X).LT.EPS) THEN
BEM12300
ATANS=PID2*Z/DABS(Z)
BEM12310
RETURN
BEM12320
ELSE
BEM12330
VAL=Z/X
BEM12340
END IF
BEM12350
ELSE
BEM12360
IF (DABS(Z).LT.EPS) THEN
BEM12370
ATANS=PID2*X/DABS(X)
BEM12380
RETURN
BEM12390
ELSE
BEM12400
VAL=X/Z
BEM12410
END IF
BEM12420
END IF
BEM12430
C
BEM12440
ATANS=DATAN(VAL)
BEM12450
NR=1
BEM12460
ELSE
BEM12470
C
BEM12480
C
Return false
BEM12490
C
BEM12500
NR=0
BEM12510
END IF
BEM12520
C
BEM12530
RETURN
BEM12540
END
BEM12550
C--------------------------------------------------------------------- BEM12560
SUBROUTINE FUNF1(ETA)
BEM12570
C--------------------------------------------------------------------- BEM12580
C0 FUNF1F
FUNF1
BEM12590
C1 PURPOSE
Compute interpolation functions for 1D-isoparametric
BEM12600
C1
element at IP of intrinsic coordinate ETA
BEM12610
C2 CALL
CALL FUN1F(ETA)
BEM12620
C3 CALL ARG. NNODE
= Number of nodes of the element
BEM12630
C3
IP
= Indice of current integration point BEM12640
C4 RET. ARG. FI(NNODE)
= Shape functions at point IP
BEM12650
C6 INT.CALL ERRORS
BEM12660
CE ERRORS
01= Incorrect number of element nodes (2 To 4).
BEM12670
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM12680
CLFUNF1 SUB. COMP. OF INTERP FUNCTION FOR 1-DIM ISOPAR. ELETS
BEM12690
C-----------------------------------------------------------------------BEM12700
C
BEM12710
IMPLICIT REAL*8 (A-H,O-Z)
BEM12720
C
BEM12730
PARAMETER (NNODMP=4)
BEM12740
C
BEM12750
CHARACTER *8 TEXTE
BEM12760
C
BEM12770
COMMON /FUNCTN/ FI(NNODMP),DUM(2*NNODMP+6),IP
BEM12780
COMMON /DELEM/ DUMZ(2*NNODMP),IDV(NNODMP),NNODE,IDUM(3)
BEM12790
C
BEM12800
DATA ONE/1.D0/,HALF/.5D0/,S/0.0625D0/,S9/0.5625D0/,RNINE/9.D0/,
BEM12810
.
THREE/3.D0/,TEXTE/'FUNF1 01'/
BEM12820

17

C
C

IF(NNODE.LT.2.OR.NNODE.GT.4) CALL ERRORS(TEXTE)


----------IF(NNODE.EQ.2) THEN
FI(1)=HALF*(ONE-ETA)
FI(2)=HALF*(ONE+ETA)
ELSE IF(NNODE.EQ.3) THEN
FI(1)=HALF*ETA*(ETA-ONE)
FI(2)=ONE-ETA*ETA
FI(3)=HALF*ETA*(ETA+ONE)
ELSE IF(NNODE.EQ.4) THEN
FI(1)=S*(ONE-ETA)*(RNINE*ETA*ETA-ONE)
FI(2)=S9*(ONE-ETA*ETA)*(ONE-THREE*ETA)
FI(3)=S9*(ONE-ETA*ETA)*(ONE+THREE*ETA)
FI(4)=S*(ONE+ETA)*(RNINE*ETA*ETA-ONE)
END IF

BEM12830
BEM12840
BEM12850
BEM12870
BEM12880
BEM12890
BEM12900
BEM12910
BEM12920
BEM12930
BEM12940
BEM12950
BEM12960
BEM12970
BEM12980

BEM12990
BEM13000
C
BEM13010
END
BEM13020
C---------------------------------------------------------------------- BEM13030
SUBROUTINE DFUNF1(ETA)
BEM13040
C--------------------------------------------------------------------- BEM13050
C0 DFUNF1F
DFUNF1
BEM13060
C1 PURPOSE
Compute 1st deriv. interpolation functions for 1D-isopar. BEM13070
C1
element at IP of intrinsic coordinate ETA
BEM13080
C2 CALL
CALL DFUNF1(ETA)
BEM13090
C3 CALL ARG. NNODE
= Number of nodes of the element
BEM13100
C3
IP
= Indice of current integration point BEM13110
C4 RET. ARG. DFI(NNODE)
= 1st der. shape functions at point IPBEM13120
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM13130
CLDFUNF1 SUB. COMP. OF 1st DER. INTERP FUNCTION FOR 1-DIM ISOPAR. ELETS BEM13140
C-----------------------------------------------------------------------BEM13150
C
BEM13160
IMPLICIT REAL*8 (A-H,O-Z)
BEM13170
C
BEM13180
PARAMETER (NNODMP=4)
BEM13190
C
BEM13200
COMMON /FUNCTN/ DVM(NNODMP),DFI(NNODMP),DUM(NNODMP+6),IP
BEM13210
COMMON /DELEM/ DUMZ(2*NNODMP),IDV(NNODMP),NNODE,IDUM(3)
BEM13220
C
BEM13230
DATA TWO/2.D0/,HALF/.5D0/,S/.0625D0/,S18/1.125D0/,S27/1.6875D0/, BEM13240
.
S81/5.0625D0/
BEM13250
C
BEM13260
IF(NNODE.EQ.2) THEN
BEM13280
DFI(1)=-HALF
BEM13290
DFI(2)= HALF
BEM13300
ELSE IF(NNODE.EQ.3) THEN
BEM13310
DFI(1)= ETA-HALF
BEM13320
DFI(2)= -TWO*ETA
BEM13330
DFI(3)= ETA+HALF
BEM13340
ELSE IF(NNODE.EQ.4) THEN
BEM13350
DFI(1)= -S27*ETA*ETA+S18*ETA+S
BEM13360
DFI(2)= S81*ETA*ETA-S18*ETA-S27
BEM13370
DFI(3)= -S81*ETA*ETA-S18*ETA+S27
BEM13380
DFI(4)= S27*ETA*ETA+S18*ETA-S
BEM13390
END IF
C
RETURN
BEM13400
C
END
BEM13410
C-----------------------------------------------------------------------BEM13420
SUBROUTINE D2FUN1 (ETA)
BEM13430
C-----------------------------------------------------------------------BEM13440
C0 D2FUN1F
D2FUNF
BEM13450
C1 PURPOSE
Compute 2nd deriv. interpolation functions for 1D-isopar. BEM13460
C1
element at IP of intrinsic coordinate ETA
BEM13470
C2 CALL
CALL D2FUN1(ETA)
BEM13480
C3 CALL ARG. NNODE
= Number of nodes of the element
BEM13490
C3
IP
= Indice of current integration point BEM13500
C4 RET. ARG. D2FI(NNODE)
= 2nd der. shape functions at point IPBEM13510
C9 94
S. GRILLI, Ocean Engng., Univ. of Rhode Island
BEM13520
CLD2FUN1 SUB. COMP. OF 2nd DER. INTERP FUNCTION FOR 1-DIM ISOPAR. ELETS BEM13530
C-----------------------------------------------------------------------BEM13540
C
BEM13550
IMPLICIT REAL*8 (A-H,O-Z)
BEM13560
RETURN

18

C
PARAMETER (NNODMP=4)
C
COMMON /FUNCTN/ DVM(2*NNODMP),D2FI(NNODMP),DUM(6),IP
COMMON /DELEM/ DUMZ(2*NNODMP),IDV(NNODMP),NNODE,IDUM(3)
C
.

DATA ZERO/0.D0/,ONE/1.D0/,TWO/2.D0/,S18/1.125D0/,S54/3.375D0/,
S162/10.125D0/

C
IF(NNODE.EQ.2) THEN
D2FI(1)=ZERO
D2FI(2)=ZERO
ELSE IF(NNODE.EQ.3) THEN
D2FI(1)=ONE
D2FI(2)=-TWO
D2FI(3)=ONE
ELSE IF(NNODE.EQ.4) THEN
D2FI(1)=-S54*ETA+S18
D2FI(2)=S162*ETA-S18
D2FI(3)=-S162*ETA-S18
D2FI(4)=S54*ETA+S18
END IF

BEM13570
BEM13580
BEM13590
BEM13600
BEM13610
BEM13620
BEM13630
BEM13640
BEM13650
BEM13670
BEM13680
BEM13690
BEM13700
BEM13710
BEM13720
BEM13730
BEM13740
BEM13750
BEM13760
BEM13770
BEM13780

C
RETURN

BEM13790

C
END
C---------------------------------------------------------------------SUBROUTINE ERRORS(TEXTE)
C--------------------------------------------------------------------C
REAL *8 TEXTE,DUM
CHARACTER *8 TEXTE,DUM
WRITE(6,10)TEXTE
STOP
10 FORMAT(1H ,'PROGRAM STOP DUE TO ERROR : ',A8)
C
END
C--------------------------------------------------------------------SUBROUTINE ANNULD(ARR,NMAX,N,M)
C-----------------------------------------------------------------IMPLICIT REAL*8(A-H,O-Z)
DIMENSION ARR(NMAX,M)
DATA ZERO/0.D0/
DO I=1,N
DO J=1,M
ARR(I,J)=ZERO
END DO
END DO
C
RETURN
C
END
C-----------------------------------------------------------------SUBROUTINE ANNULU(VEC,N)
C-----------------------------------------------------------------IMPLICIT REAL*8(A-H,O-Z)
DIMENSION VEC(N)
DATA ZERO/0.D0/
DO I=1,N
VEC(I)=ZERO
END DO
C
RETURN
C
END

19

BEM13800
BEM13810
BEM13820
BEM13830
BEM13840
BEM13840
BEM13850
BEM13860
BEM13870
BEM13880
BEM13890
BEM13900
BEM13910
BEM13920
BEM13930
BEM13940
BEM13950
BEM13960
BEM13970
BEM13980
BEM13990
BEM14000
BEM14010
BEM14020
BEM14030
BEM14040
BEM14050
BEM14060
BEM14070
BEM14080
BEM14090
BEM14100
BEM14110
BEM14120

Das könnte Ihnen auch gefallen