19

Click here to load reader

BEM1.F

Embed Size (px)

DESCRIPTION

fortran

Citation preview

  • 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)BEM00030C-----------------------------------------------------------------------BEM00040C0 APPELF APPEL BEM00050C1 PURPOSE Performs the main stages of the BEM by calling the BEM00060C1 corresponding modules BEM00070C2 CALL CALL APPEL(X,Z,ZKQG,ZKUG,ZKQL,ZKUL,PG,ZKG,PU,PQ,C,LXZI, BEM00080C2 MDELEM,VN1,VN2,VN3,VN4,NADR,MADR,VWORK,IWORK,NPROB) BEM00090C3 CALL ARG. X(NOM),Z(NOM) = Coordinates of discretization nodes BEM00100C3 LXZI(NOM) = Addresses of possible double nodes BEM00110C3 NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM00120C3 MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR, BEM00130C3 NINTS,NSIDE) BEM00140C3 C(NOM) = Coefficients c incase of dir. comp. BEM00150C3 ZKQL(NOM,NNODE) = Local Kq matrix BEM00160C3 ZKUL(NOM,NNODE) = Local Ku matrix BEM00170C3 ZKQG(NOM,NOM) = Global Kq matrix BEM00180C3 ZKUG(NOM,NOM) = Global Ku matrix BEM00190C3 ZKG(NOM,NOM),PG(NOM)= Global system matrix and vector BEM00200C3 PU(NOM),PQ(NOM) = Boundary values of u and q BEM00210C3 VN1(N1),VN2(N2) = Boundary conditions on N1, N2 BEM00220C3 VN3(N3),VN4(N4) = Boundary conditions on N3, N4 BEM00230C3 VWORK(3*NOM) = Working vector for k(2) comput. BEM00240C3 IWORK(NOM) = Working vector for k(2) comput. BEM00250C3 NOM,NELEM = Discr. nb. of nodes and elements BEM00260C3 NOMM,NELMM = Discr. max nb. of nodes and elementsBEM00270C3 ILISS = Mode of C computation (0/1) BEM00280C3 NNODM = Discr. max nb. of nodes per element BEM00290C3 XLOC(NNODE) = X-coordinates of element IE nodes BEM00300C3 ZLOC(NNODE) = Z-coordinates of element IE nodes BEM00310C3 NODE(NNODE) = Nodes of element IE BEM00320C3 NINTR,NINTS = Nb. of regular and singular int. ptsBEM00330C3 N1,N2,N3,N4 = Nb. of nodes of bound. 1,2,3,4 BEM00340C3 IO5,IO6,NSAVE = Input,output and save file numbers BEM00350C3 ISAVE = Save results and postprocess (1) BEM00360C3 ICOND = Compute cond. number k(2) (1) BEM00370C3 RCOND = Condition number k(2) BEM00380C3 NPROB = Nmber of problems to be solved BEM00390C4 RET. ARG. PU,PQ... BEM00400C6 INT.CALL INPUTD,BEMK,ASSEMK,ASSEMP,DBNOD,CONDNO,SOLVE,SORT,OUTPUT, BEM00410C6 ERRORS BEM00420C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM00430CLAPPEL SUB. WHICH PERFORMS THE MAIN STAGES OF THE 2D-BEM BEM00440C-----------------------------------------------------------------------BEM00450C BEM00460 IMPLICIT REAL*8(A-H,O-Z) BEM00470C BEM00480 PARAMETER (NNODMP=4) BEM00490C BEM00500 INTEGER *2 NADR(NOM),MADR(NOM) BEM00510C 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 BEM00560C BEM00570C.....Problem matrices and vectors BEM00580C 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) BEM00620C BEM00630C.....Domain geometry and topology BEM00640C BEM00650 DIMENSION X(NOM),Z(NOM),C(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM) BEM00660C BEM00670 DATA ZERO/0.D0/,ONE/1.D0/ BEM00680C BEM00690C=====General loop on the problems BEM00700C BEM00710 DO IPROB=1,NPROB BEM00720C BEM00730C........Input of general data, analysis of boundary, double nodes, BEM00740C Initial conditions BEM00750C BEM00760

    1

  • CALL INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR,ICOND) BEM00770C ---------- BEM00780C BEM00790 IF (ISAVE.EQ.1) THEN BEM00800 REWIND NSAVE BEM00810 END IF BEM00820C BEM00830C........Formation of the matrices Ku and Kq, and system matrix K BEM00840C BEM00850 CALL BEMK(ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR,MADR) BEM00860C --------- BEM00870C BEM00880C........Assembling of the general system matrix ZKG BEM00890C BEM00900 CALL ASSEMK(ZKG,ZKUG,ZKQG,NADR) BEM00910C ----------- BEM00920C BEM00930C........Construction of the system right hand side PG BEM00940C BEM00950 CALL ASSEMP(PG,ZKUG,ZKQG,NADR,VN1,VN2,VN3,VN4) BEM00960C ----------- BEM00970C BEM00980C........Double nodes compatibility conditions on ZKG and PG BEM00990C BEM01000 CALL DBNOD(ZKG,PG,VN1,NADR,LXZI) BEM01010C ---------- BEM01020C BEM01030C........Condition number computation if ICOND=1 BEM01040C (!: ZQUG and ZKQG are working matrix from now) BEM01050C BEM01060 CALL CONDNO(ZKG,ZKUG,ZKQG,VWORK,IWORK,ICOND,RCOND) BEM01070C ----------- BEM01080C BEM01090C........Solving of the system BEM01100C BEM01110 CALL SOLVE(ZKG,PG,1) BEM01120C ---------- BEM01130C BEM01140C........Sort results BEM01150C BEM01160 CALL SORT(PG,PU,PQ,VN1,VN2,VN3,VN4,NADR) BEM01170C --------- BEM01180C BEM01190C........Post process and print results from Laplace' solution. BEM01200C BEM01210 CALL OUTPUT(PU,PQ,X,Z,MDELEM,ICOND,RCOND) BEM01220 CALL OUT2(PU,PQ,X,Z,MDELEM,ICOND,RCOND) BEM01220

    C ----------- BEM01230C BEM01240 END DO BEM01250C BEM01260 RETURN BEM01270C BEM01280 END BEM01290C-----------------------------------------------------------------------BEM01300 SUBROUTINE INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR,ICOND) BEM01310C-----------------------------------------------------------------------BEM01320C0 INPUTF INPUT BEM01330C1 PURPOSE Reads the general datas for the 2D-BEM, i.e. the nodes BEM01340C1 coord.,elements definition, integrat. and B.C. informationBEM01350C2 CALL CALL INPUT(X,Z,MDELEM,LXZI,VN1,VN2,VN3,VN4,NADR,MADR) BEM01360C3 (CALL ARG. X(NOM),Z(NOM) = Coordinates of discretization nodes BEM01370C3 (RET. LXZI(NOM) = Addresses of possible double nodes BEM01380C3 NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM01390C3 MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR, BEM01400C3 NINTS,NSIDE) BEM01410C3 VN1(N1),VN2(N2) = Boundary conditions on N1, N2 BEM01420C3 VN3(N3),VN4(N3) = Boundary conditions on N3, N4 BEM01430C3 NOM,NELEM = Discr. nb. of nodes and elements BEM01440C3 NOMM,NELMM = Discr. max nb. of nodes and elementsBEM01450C3 NNODM = Discr. max nb. of nodes per element BEM01460C3 NNODE,NSIDE = Current nb. of nodes and code of el.BEM01470C3 NINTR,NINTS = Nb. of regular and singular int. ptsBEM01480C3 N1,N2,N3,N4 = Nb. of nodes of bound. 1,2,3,4 BEM01490C3 IO5,IO6,NSAVE = Input,output and save file numbers BEM01500

    2

  • C3 ISAVE = Save results and postprocess (1) BEM01510C3 ICOND = Compute cond. number k(2) (1) BEM01520C6 INT.CALL ERRORS BEM01530CE ERRORS 01= General data are out of range BEM01540CE 02= Element nodes are out of range BEM01550CE 03= End of data in input file BEM01560C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM01570CLINPUT SUB. WHICH READS INPUT DATA FOR THE 2D-BEM BEM01580C-----------------------------------------------------------------------BEM01590C BEM01600 IMPLICIT REAL *8 (A-H,O-Z) BEM01610C BEM01620 PARAMETER (NNODMP=4) BEM01630C BEM01640 INTEGER *2 NADR(NOM),MADR(NOM) BEM01650 CHARACTER *8 TEXTE(3) BEM01660C BEM01670 DIMENSION X(NOM),Z(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM),VN1(N1), BEM01680 . VN2(N2),VN3(N3),VN4(N4) BEM01690C BEM01700 COMMON /MAILLE/ NOMM,NELMM,NOM,NELEM,NNODM,N1,N2,N3,N4,I1,I2, BEM01710 . I3,I4,ILISS,ISAVE,IO5,IO6,NSAVE BEM01720C BEM01730 DATA EPS /1.D-06/,SOIX/60.D0/,TEXTE/'INPUT 01', BEM01740 . 'INPUT 02','INPUT 03'/ BEM01750C BEM01760C.....Initialization BEM01770C BEM01780 I1=0 BEM01790 I2=0 BEM01800 I3=0 BEM01810 I4=0 BEM01820 N1=0 BEM01830 N2=0 BEM01840 N3=0 BEM01850 N4=0 BEM01860C BEM01870C.....General data input and check of data BEM01880C BEM01890 READ(IO5,1000,END=200) NOM,NELEM,ILISS,ISAVE,ICOND BEM01900C BEM01910 IF((NOM.GT.NOMM.OR.NOM.LT.0).OR.(NELEM.GT.NELMM.OR.NELEM.LT.0)) BEM01920 . THEN BEM01930 CALL ERRORS(TEXTE(1)) BEM01940C ----------- BEM01950 END IF BEM01960C 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)) BEM02000C ----------- BEM02010 END IF BEM02020C BEM02030C.....General title and general data printing BEM02040C BEM02050 WRITE(IO6,2000) BEM02060 WRITE(IO6,2010) NOM,NELEM,ILISS,ISAVE,ICOND BEM02070C BEM02080C.....Nodal Coordinates and initial conditions input BEM02090C BEM02100 READ(IO5,1010,END=200)(X(I),Z(I),I=1,NOM) BEM02110C BEM02120C.....Elements input and checking BEM02130C BEM02140C Print title BEM02150C BEM02160 WRITE(IO6,2040) BEM02170C BEM02180 INADR=0 BEM02190 DO IE=1,NELEM BEM02200C BEM02210 READ(IO5,1020,END=200)(MDELEM(I,IE),I=1,NNODMP+4) BEM02220C BEM02230 NSIDE=MDELEM(NNODMP+4,IE) BEM02240 NNODE=MDELEM(NNODMP+1,IE) BEM02250C BEM02260

    3

  • IF((NSIDE.LT.1.OR.NSIDE.GT.4).OR.(NNODE.LT.2.OR.NNODE.GT.4)) BEM02270 . THEN BEM02280 CALL ERRORS(TEXTE(2)) BEM02290C ----------- BEM02300 END IF BEM02310C BEM02320 DO I=1,NNODE BEM02330 IF(MDELEM(I,IE).LE.0.OR.MDELEM(I,IE).GT.NOM) THEN BEM02340 CALL ERRORS(TEXTE(2)) BEM02350C ----------- BEM02360 END IF BEM02370 END DO BEM02380C BEM02390C Print element IE data BEM02400C BEM02410 WRITE(IO6,2050) IE,NSIDE,MDELEM(NNODMP+2,IE),MDELEM(NNODMP+3, BEM02420 . IE),(MDELEM(I,IE),I=1,NNODE) BEM02430 IF((DFLOAT(IE+10)/SOIX-DFLOAT((IE+10)/60)).LT.EPS) THEN BEM02440 WRITE(IO6,2060) BEM02450 END IF BEM02460C BEM02470C........Boundary conditions, localisation BEM02480C BEM02490 IINTR=0 BEM02500 DO I=1,NNODE BEM02510 L=MDELEM(I,IE) BEM02520 INADR=INADR+1 BEM02530 IINTR=IINTR+1 BEM02540 JLOC=INADR BEM02550 DO J=1,INADR-1 BEM02560 IF(MADR(J).EQ.L) THEN BEM02570 JLOC=J BEM02580 INADR=INADR-1 BEM02590 IINTR=IINTR-1 BEM02600 END IF BEM02610 END DO BEM02620 MADR(JLOC)=L BEM02630 END DO BEM02640C BEM02650 IF(NSIDE.EQ.1) THEN BEM02660 N1=N1+1 BEM02670 I1=I1+IINTR BEM02680 ELSE IF(NSIDE.EQ.2) THEN BEM02690 N2=N2+1 BEM02700 I2=I2+IINTR BEM02710 ELSE IF(NSIDE.EQ.3) THEN BEM02720 N3=N3+1 BEM02730 I3=I3+IINTR BEM02740 ELSE IF(NSIDE.EQ.4) THEN BEM02750 N4=N4+1 BEM02760 I4=I4+IINTR BEM02770 END IF END DO BEM02780 WRITE(IO6,2070) N1,I1,N2,I2,N3,I3,N4,I4 BEM02790C BEM02800C.....Initializations BEM02810C BEM02820 N1=I1 BEM02830 N2=I2 BEM02840 N3=I3 BEM02850 N4=I4 BEM02860C BEM02870C.....Read boundary conditions BEM02880C BEM02890 DO J=1,N1/8+1 BEM02900 READ(IO5,*,END=200) (VN1(I),I=(J-1)*8+1,MIN(J*8,N1)) BEM02910 END DO BEM02920 DO J=1,N2/8+1 BEM02930 READ(IO5,*,END=200) (VN2(I),I=(J-1)*8+1,MIN(J*8,N2)) BEM02940 END DO BEM02950 DO J=1,N3/8+1 BEM02960 READ(IO5,*,END=200) (VN3(I),I=(J-1)*8+1,MIN(J*8,N3)) BEM02970 END DO BEM02980 DO J=1,N4/8+1 BEM02990 READ(IO5,*,END=200) (VN4(I),I=(J-1)*8+1,MIN(J*8,N4)) BEM03000 END DO BEM03010

    4

  • C BEM03020C.....Double nodes localisation BEM03030C 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 BEM03220C BEM03230 RETURN BEM03240C BEM03250C End of data BEM03260C BEM03270 200 CALL ERRORS(TEXTE(3)) BEM03280C ----------- BEM03290C BEM03300 STOP BEM03310C BEM03320 1000 FORMAT(5I5) BEM03330 1010 FORMAT(2F10.0) BEM03340 1020 FORMAT(8I5) BEM03350C 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) BEM03660C BEM03670 END BEM03680C-----------------------------------------------------------------------BEM03690 SUBROUTINE BEMK(ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR, BEM03700 . MADR) BEM03710C-----------------------------------------------------------------------BEM03720C0 BEMKF BEMK BEM03730C1 PURPOSE Compute all the Ku and Kq, c (direct or rigid mode: ILISS BEM03740C1 (0/1)) for the 2D-BEM, and introduce c into Kq BEM03750C2 CALL CALL BEMK(ZKG,ZKUG,ZKQG,C,X,Z,MDELEM,LXZI,ZKQL,ZKUL,NADR, BEM03760C2 MADR) BEM03770

    5

  • C3 CALL ARG. X(NOM),Z(NOM) = Coordinates of discretization nodes BEM03780C3 LXZI(NOM) = Addresses of possible double nodes BEM03790C3 NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM03800C3 MDELEM(NP+4,NELEM) = Elements data(Nodes,NNODE,NINTR, BEM03810C3 NINTS,NSIDE) BEM03820C3 C(NOM) = Coefficients c incase of dir. comp. BEM03830C3 ZKQL(NOM,NNODE) = Local Kq matrix of element IE BEM03840C3 ZKUL(NOM,NNODE) = Local Ku matrix of element IE BEM03850C3 XLOC(NNODE) = X-coordinates of element IE nodes BEM03860C3 ZLOC(NNODE) = Z-coordinates of element IE nodes BEM03870C3 NODE(NNODE) = Nodes of element IE BEM03880C3 ZKQG(NOM,NOM) = Global Kq matrix BEM03890C3 ZKUG(NOM,NOM) = Global Ku matrix BEM03900C3 NOM,NELEM = Discr. nb. of nodes and elements BEM03910C3 NOMM = Discr. max nb. of nodes BEM03920C3 NNODM = Discr. max nb. of nodes per element BEM03930C3 NINTR,NINTS = Nb. of regular and singular int. ptsBEM03940C3 N1,N2,N3,N4 = Nb. of nodes of bound. 1,2,3,4 BEM03950C3 NSAVE = Save file number BEM03960C4 RET. ARG. ZKUG,ZKQG,NADR,MADR BEM03970C6 INT.CALL BIMAT,ASSEML,INTERCI,ANNULU,ANNULD BEM03980C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM03990CLBEMK SUB. WHICH COMPUTES THE MATRIX Ku,Kq AND K FOR THE 2D-BEM BEM04000C-----------------------------------------------------------------------BEM04010C BEM04020 IMPLICIT REAL*8(A-H,O-Z) BEM04030C BEM04040 PARAMETER (NNODMP=4) BEM04050C BEM04060 INTEGER *2 NADR(NOM),MADR(NOM) BEM04070C 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 BEM04120C BEM04130C.....Procedure vectors and matrices dimensioning BEM04140C BEM04150C Domain geometry and topology BEM04160C BEM04170 DIMENSION X(NOM),Z(NOM),MDELEM(NNODMP+4,NELEM),LXZI(NOM) BEM04180C BEM04190C Working matrices BEM04200C BEM04210 DIMENSION ZKUL(NOMM,NNODM),ZKQL(NOMM,NNODM) BEM04220C BEM04230C Problem matrices (results of the procedure) BEM04240C BEM04250 DIMENSION ZKUG(NOMM,NOM),ZKQG(NOMM,NOM),C(NOM) BEM04260C BEM04270C.....Initialize the system matrices, and adressing variables BEM04280C BEM04290 CALL ANNULD(ZKQG,NOMM,NOM,NOM) BEM04300C ----------- BEM04310 CALL ANNULD(ZKUG,NOMM,NOM,NOM) BEM04320C ----------- BEM04330 CALL ANNULU(C,NOM) BEM04340C ----------- BEM04350C BEM04360 DO I=1,NOM BEM04370 NADR(I)=0 BEM04380 END DO BEM04390C BEM04400 I1=0 BEM04410 I2=0 BEM04420 I3=0 BEM04430 I4=0 BEM04440C BEM04450C.....Loop on the elements, local computations, assembling BEM04460C BEM04470 DO IE=1,NELEM BEM04480C BEM04490C Local values assigned to element IE BEM04500C BEM04510 NSIDE=MDELEM(NNODMP+4,IE) BEM04520 NNODE=MDELEM(NNODMP+1,IE) BEM04530

    6

  • DO J=1,NNODE BEM04540 NODE(J)=MDELEM(J,IE) BEM04550 XLOC(J)=X(NODE(J)) BEM04560 ZLOC(J)=Z(NODE(J)) BEM04570 END DO BEM04580 NINTR=MDELEM(NNODMP+2,IE) BEM04590 NINTS=MDELEM(NNODMP+3,IE) BEM04600C BEM04610C Computation of local matrices, save geometry and shape funct. BEM04620C on file NSAVE BEM04630C BEM04640 CALL BIMAT(ZKQL,ZKUL,C,X,Z,LXZI) BEM04650C ---------- BEM04660C BEM04670C Global assembling BEM04680C BEM04690 CALL ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR) BEM04700C ----------- BEM04710C BEM04720 END DO BEM04730C BEM04740C.....Introduction of C(I) in the system matrices, and inverse assembl. BEM04750C BEM04760 CALL INTRCI(ZKQG,C,NADR,MADR) BEM04770C ----------- BEM04780C BEM04790 RETURN BEM04800C BEM04810 END BEM04820C-----------------------------------------------------------------------BEM04830 SUBROUTINE BIMAT(ZKQL,ZKUL,C,X,Z,LXZI) BEM04840C-----------------------------------------------------------------------BEM04850C0 BIMATF BIMAT BEM04860C1 PURPOSE Compute the local Kul and Kql to the elemt IE and c if BEM04870C1 direct (ILISS=0) for the 2D-BEM BEM04880C2 CALL CALL BIMAT(ZKQL,ZKUL,C,X,Z,LXZI) BEM04890C3 CALL ARG. X(NOM),Z(NOM) = Coordinates of discretization nodes BEM04900C3 LXZI(NOM) = Addresses of possible double nodes BEM04910C3 C(NOM) = Coefficients c in case of dir. comp.BEM04920C3 NOM,NELEM = Discr. nb. of nodes and elements BEM04930C3 NOMM = Discr. max nb. of nodes BEM04940C3 NNODM = Discr. max nb. of nodes per element BEM04950C3 NSAVE = Save file number BEM04960C3 ZKQL(NOM,NNODE) = Local Kq matrix of element IE BEM04970C3 ZKUL(NOM,NNODE) = Local Ku matrix of element IE BEM04980C3 NINTR,NINTS = Nb. of reg. and sing. int. pts of IEBEM04990C3 SGCI,SGKQ = Local particular integration on IE BEM05000C3 IP = current integration point of IE BEM05010C3 NODE(NNODE) = Nodes of element IE BEM05020C3 FI(NNODE) = Shape functions and ) At point BEM05030C3 DFI(NNODE),D2FI() = their derivatives ) IP BEM05040C3 WEIGHT = current integr. point integr. weightBEM05050C3 XIP,ZIP = Current integr. point coordinates BEM05060C3 ZNX,ZNZ = Current integr. point normal vector BEM05070C3 DS = Current integr. point jacobian BEM05080C4 RET. ARG. ZKUL,ZKQL BEM05090C6 INT.CALL FUNC1D,CARAC1,SGDUDN BEM05100C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM05110CLBIMAT SUB. WHICH COMPUTES THE MATRIX Kul AND Kql OF IE FOR THE 2D-BEM BEM05120C-----------------------------------------------------------------------BEM05130C BEM05140 IMPLICIT REAL*8(A-H,O-Z) BEM05150C BEM05160 PARAMETER (NNODMP=4) BEM05170C 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 BEM05220C BEM05230 DIMENSION ZKUL(NOMM,NNODE),ZKQL(NOMM,NNODE),C(NOM) BEM05240C BEM05250 DIMENSION X(NOM),Z(NOM),LXZI(NOM) BEM05260C BEM05270 DIMENSION SGCI(NNODMP),SGKQ(NNODMP,NNODMP) BEM05280C BEM05290

    7

  • DATA ONE/1.D0/,TWO/2.D0/,ZERO/0.D0/,HALF/.5D0/, BEM05300 . PII2/.1591549430918953D0/ BEM05310C BEM05320C Boundary integrals on element IE BEM05330C BEM05340C Initialisation of local matrices BEM05350C BEM05360 DO J=1,NNODE BEM05370 DO I=1,NOM BEM05380 ZKQL(I,J)=ZERO BEM05390 ZKUL(I,J)=ZERO BEM05400 END DO BEM05410 END DO BEM05420C BEM05430C Regular integration BEM05440C BEM05450 DO IP=1,NINTR BEM05460 CALL FUNC1D(0,0,ETA) BEM05470C ----------- BEM05480 CALL CARAC1 BEM05490C ----------- BEM05500C BEM05510C Save geometry and shape functions on file NSAVE BEM05520C BEM05530 IF(ISAVE.EQ.1) THEN BEM05540 WRITE(NSAVE) ETA,XIP,ZIP,(FI(I),DFI(I),D2FI(I),I=1,NNODE), BEM05550 . DS,WEIGHT,ZNX,ZNZ BEM05560 END IF BEM05570C BEM05580C Computation of ZKUL, ZKQL BEM05590C BEM05600 DS=DS*WEIGHT BEM05610 DO I=1,NOM BEM05620 XX=XIP-X(I) BEM05630 ZZ=ZIP-Z(I) BEM05640 R=DSQRT(XX*XX+ZZ*ZZ) BEM05650C BEM05660C Computation of Green functions BEM05670C BEM05680 DUDN=-PII2*(ZNX*XX+ZNZ*ZZ)/(R*R) BEM05690 U=DLOG(R) BEM05700C BEM05710C Kernel transformation, in case of I on IE BEM05720C BEM05730 DO J=1,NNODE BEM05740 IF (I.EQ.NODE(J)) THEN BEM05750 ETAI=(TWO*J-NNODE-ONE)/(NNODE-ONE) BEM05760 ETAP=DABS(ETA-ETAI)*HALF BEM05770 U=U-DLOG(ETAP) BEM05780 DUDN=ZERO BEM05790 END IF BEM05800 END DO BEM05810 U=-U*PII2 BEM05820C BEM05830 C(I)=C(I)-DUDN*DS BEM05840 DO J=1,NNODE BEM05850 ZKUL(I,J)=ZKUL(I,J)+FI(J)*U*DS BEM05860 ZKQL(I,J)=ZKQL(I,J)+FI(J)*DUDN*DS BEM05870 END DO BEM05880 END DO BEM05890 END DO BEM05900C BEM05910C Singular integrals for ZKUL BEM05920C BEM05930 DO I=1,NNODE BEM05940 M=NODE(I) BEM05950C BEM05960C Second regular part of the singular integrals, and BEM05970C Singular part of the singular integrals BEM05980C BEM05990 DO IP=1,NINTS BEM06000 DO NSG=1,2 BEM06010 DO K=1,2 BEM06020 NSGC=NSG*(2*K-3) BEM06030 CALL FUNC1D(NSGC,I,ETA) BEM06040C ----------- BEM06050

    8

  • CALL CARAC1 BEM06060C ----------- BEM06070 DS=DS*WEIGHT BEM06080 DO J=1,NNODE BEM06090 ZKUL(M,J)=ZKUL(M,J)-FI(J)*DS*PII2 BEM06100 END DO BEM06110 END DO BEM06120 END DO BEM06130 END DO BEM06140 END DO BEM06150C BEM06160C Particular Integral for ZKQL, C (NNODE > 2) BEM06170C BEM06180 IF(NNODE.GT.2) THEN BEM06190 CALL SGDUDN(SGKQ,SGCI) BEM06200C ----------- 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 BEM06290C BEM06300C Double nodes, taking into account for the sing. and part. integ. BEM06310C 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 BEM06410C BEM06420 RETURN BEM06430C BEM06440 END BEM06450C---------------------------------------------------------------------- BEM06460 SUBROUTINE ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR) BEM06470C---------------------------------------------------------------------- BEM06480C0 ASSEMLF ASSEML BEM06490C1 PURPOSE Assemble local Kul and Kql of the elemt IE in the global BEM06500C1 matrix Ku and Kq for the 2D-BEM(in order N1,N2,N3,N4), BEM06510C1 and set NADR BEM06520C2 CALL CALL ASSEML(ZKQG,ZKUG,ZKQL,ZKUL,NADR) BEM06530C3 CALL ARG. NOM = Discr. nb. of nodes BEM06540C3 NOMM = Discr. max nb. of nodes BEM06550C3 N1,N2,N3,N4 = Nb. of nodes of bound. 1,2,3,4 BEM06560C3 ZKQG(NOM,NOM) = Global Kq matrix BEM06570C3 ZKUG(NOM,NOM) = Global Ku matrix BEM06580C3 ZKQL(NOM,NNODE) = Local Kq matrix of element IE BEM06590C3 ZKUL(NOM,NNODE) = Local Ku matrix of element IE BEM06600C3 NODE(NNODE) = Nodes of element IE BEM06610C4 RET. ARG. ZKUG,ZKQG,NADR BEM06620C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM06630CLASSEML SUB. WHICH ASSEMBLES MATRIX Kul AND Kql OF IE FOR THE 2D-BEM BEM06640C-----------------------------------------------------------------------BEM06650C BEM06660 IMPLICIT REAL*8(A-H,O-Z) BEM06670C BEM06680 PARAMETER (NNODMP=4) BEM06690C BEM06700 INTEGER *2 NADR(NOM) BEM06710C 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 BEM06740C BEM06750 DIMENSION ZKQG(NOMM,NOM),ZKUG(NOMM,NOM),ZKQL(NOMM,NNODE), BEM06760 . ZKUL(NOMM,NNODE) BEM06770C BEM06780 DATA ONE/1.D0/,HALF/.5D0/ BEM06790C BEM06800 DO J=1,NNODE BEM06810

    9

  • K=NODE(J) BEM06820C IF(NSIDE.EQ.1) THEN BEM06830C BEM06840C...........Boundary NSIDE=1 BEM06850C BEM06860 I1P=I1 BEM06870 I1=I1+1 BEM06880 KLOC=I1 BEM06890 DO L=1,I1P BEM06900 IF(NADR(L).EQ.K) THEN BEM06910 KLOC=L BEM06920 I1=I1-1 BEM06930 END IF BEM06940 END DO BEM06950 NADR(KLOC)=K BEM06960 DO I=1,NOM BEM06970 ZKUG(I,KLOC)=ZKUG(I,KLOC)+ZKUL(I,J) BEM06980 ZKQG(I,KLOC)=ZKQG(I,KLOC)+ZKQL(I,J) BEM06990 END DO BEM07000 ELSE IF(NSIDE.EQ.2) THEN BEM07010C BEM07020C...........Boundary NSIDE=2 BEM07030C BEM07040 I2P=I2 BEM07050 I2=I2+1 BEM07060 KLOC=I2 BEM07070 DO L=1,I2P BEM07080 IF(NADR(L+N1).EQ.K) THEN BEM07090 KLOC=L BEM07100 I2=I2-1 BEM07110 END IF BEM07120 END DO BEM07130 NADR(KLOC+N1)=K BEM07140 DO I=1,NOM BEM07150 ZKUG(I,KLOC+N1)=ZKUG(I,KLOC+N1)+ZKUL(I,J) BEM07160 ZKQG(I,KLOC+N1)=ZKQG(I,KLOC+N1)+ZKQL(I,J) BEM07170 END DO BEM07180 ELSE IF(NSIDE.EQ.3) THEN BEM07190C BEM07200C...........Boundary NSIDE=3 BEM07210C BEM07220 I3P=I3 BEM07230 I3=I3+1 BEM07240 KLOC=I3 BEM07250 NC=N1+N2 BEM07260 DO L=1,I3P BEM07270 IF(NADR(L+NC).EQ.K) THEN BEM07280 KLOC=L BEM07290 I3=I3-1 BEM07300 END IF BEM07310 END DO BEM07320 NADR(KLOC+NC)=K BEM07330 DO I=1,NOM BEM07340 ZKUG(I,KLOC+NC)=ZKUG(I,KLOC+NC)+ZKUL(I,J) BEM07350 ZKQG(I,KLOC+NC)=ZKQG(I,KLOC+NC)+ZKQL(I,J) BEM07360 END DO BEM07370 ELSE IF(NSIDE.EQ.4) THEN BEM07380C BEM07390C...........Boundary NSIDE=4 BEM07400C BEM07410 I4P=I4 BEM07420 I4=I4+1 BEM07430 KLOC=I4 BEM07440 NC=N1+N2+N3 BEM07450 DO L=1,I4P BEM07460 IF(NADR(L+NC).EQ.K) THEN BEM07470 KLOC=L BEM07480 I4=I4-1 BEM07490 END IF BEM07500 END DO BEM07510 NADR(KLOC+NC)=K BEM07520 DO I=1,NOM BEM07530 ZKUG(I,KLOC+NC)=ZKUG(I,KLOC+NC)+ZKUL(I,J) BEM07540 ZKQG(I,KLOC+NC)=ZKQG(I,KLOC+NC)+ZKQL(I,J) BEM07550 END DO BEM07560

    10

  • END IF END DO BEM07570C BEM07580 RETURN BEM07590C BEM07600 END BEM07610C---------------------------------------------------------------------- BEM07620 SUBROUTINE INTRCI(ZKQG,C,NADR,MADR) BEM07630C---------------------------------------------------------------------- BEM07640C0 INTRCIF INTRCI BEM07650C1 PURPOSE Introduce c coefficients into Kq either from their direct BEM07660C1 knowledge (ILISS=0) or by the "rigid mode" method (=1). BEM07670C1 Set inverse adressing vector MADR BEM07680C2 CALL CALL INTRCI(ZKQG,C,NADR,MADR) BEM07690C3 CALL ARG. NOM = Discr. nb. of nodes BEM07700C3 NOMM = Discr. max nb. of nodes BEM07710C3 ILISS = Mode of C computation (0/1) BEM07720C3 C(NOM) = Coefficients c incase of dir. comp. BEM07730C3 ZKQG(NOM,NOM) = Global Kq matrix of element IE BEM07740C3 NADR(NOM),MADR(NOM) = Addressing and inverse add. of nodesBEM07750C4 RET. ARG. ZKQG,MADR BEM07760C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM07770CLINTRCI SUB. WHICH INTRODUCES C INTO Kq FOR THE 2D-BEM BEM07780C-----------------------------------------------------------------------BEM07790C BEM07800 IMPLICIT REAL*8(A-H,O-Z) BEM07810C BEM07820 INTEGER *2 NADR(NOM),MADR(NOM) BEM07830C BEM07840 COMMON /MAILLE/ NOMM,IDUM,NOM,IDU(10),ILISS,IDV(4) BEM07850C BEM07860 DIMENSION ZKQG(NOMM,NOM),C(NOM) BEM07870C BEM07880 DATA ZERO/0.D0/ BEM07890C BEM07900C Set inverse adressing vector BEM07910C BEM07920 DO I=1,NOM BEM07930 MADR(NADR(I))=I BEM07940 END DO BEM07950C BEM07960 DO I=1,NOM BEM07970 L=NADR(I) BEM07980 IF(ILISS.EQ.0) THEN BEM07990C BEM08000C Direct C(I) BEM08010C BEM08020 ZKQG(L,I)=ZKQG(L,I)+C(L) BEM08030 ELSE BEM08040C BEM08050C C(I) by the rigid mode technique BEM08060C 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 BEM08150C BEM08160 RETURN BEM08170C BEM08180 END BEM08190C-----------------------------------------------------------------------BEM08200 SUBROUTINE FUNC1D (NSG,IN,ETA) BEM08210C-----------------------------------------------------------------------BEM08220C0 FUNC1DF FUNC1D BEM08230C1 PURPOSE Compute interpolation functions for 1D-isoparametric BEM08240C1 elements, and their derivatives at integ. point IP BEM08250C2 CALL CALL FUNC1D(NSG,IN,ETA) BEM08260C3 CALL ARG. NNODE = Number of nodes of the element BEM08270C3 NINTR,NINTS = Number of reg. or sing. int. points BEM08280C3 IP = Indice of current integration point BEM08290C3 NSG=0 = Regular GAUSS quadrature BEM08300C3 NSG
  • C3 NSG>0 = BERTHOD-ZABOROWISKY sing. integr. BEM08320C4 RET. ARG. FI(NNODE),ETA = Shape functions and ) At point BEM08330C4 DFI(NNODE),D2FI() = their derivatives ) IP BEM08340C4 WEIGHT = Integration weight BEM08350C6 INT.CALL FUNF1,DFUNF1,D2FUN1,ERRORS BEM08360CE ERRORS 01= Incorrect number of integration points (2 To 6). BEM08370CE 02= Incorrect number of elements nodes (2 to NDM) BEM08380CE 03= Indice of integration point out of order BEM08390C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM08400CLFUNC1D SUB. COMP. OF INTERP FUNCTION FOR 1-DIM ISOPAR. ELETS BEM08410C-----------------------------------------------------------------------BEM08420C BEM08430 IMPLICIT REAL*8 (A-H,O-Z) BEM08440C BEM08450 PARAMETER (NNODMP=4) BEM08460C BEM08470 CHARACTER *8 TEXTE1,TEXTE2,TEXTE3 BEM08480C BEM08490 DIMENSION XIP(5,3),WIP(5,3),XIS(6,5),WIS(6,5) BEM08500C 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 BEM08540C 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/ BEM08890C BEM08900 IF (NNODE.LT.2.OR.NNODE.GT.4) CALL ERRORS (TEXTE2) BEM08910C ----------- BEM08920 NINT=NINTR BEM08930 IF (NSG.NE.0) NINT=NINTS BEM08940 IF (NINT.LT.2.OR.NINT.GT.6) CALL ERRORS (TEXTE1) BEM08950C ----------- BEM08960 IF (IP.LT.1.OR.IP.GT.NINT) CALL ERRORS (TEXTE3) BEM08970C ----------- BEM08980C BEM08990 IF(NSG.LE.0) THEN BEM09000C BEM09010C Gauss quadrature, degree 3 to 11 (2 to 6 nodes)(NSG
  • M = 1 BEM09080 ELSE IF(NINT.EQ.3) THEN BEM09090C...........3 integration points BEM09100 K = IP - 2 BEM09110 M = 5 + IP * (IP-4) BEM09120 ELSE IF(NINT.EQ.4) THEN BEM09130C...........4 integration points BEM09140 K = 5 + IP * ( IP * (15 - 2*IP) - 31 ) / 3 BEM09150 M = 4 + IP * (IP-5) / 2 BEM09160 ELSE IF(NINT.EQ.5) THEN BEM09170C...........5 integration points BEM09180 K = 1 + IP * ((9-IP) * IP - 20) / 6 BEM09190 M = 27 + IP * ( IP * (347 + IP * (7*IP-84)) - 570 ) /12 BEM09200 ELSE IF(NINT.EQ.6) THEN BEM09210C...........6 integration points BEM09220 K = -21 + IP * (2614 + IP * (IP * (680+IP*(6*IP-105)) . - 1995))/60 BEM09230 M = 2 + IP * (70 + IP * ( IP * (14-IP) - 59 )) / 24 BEM09240 END IFC BEM09250 ETA = K * XIP(NINT-1,M) BEM09260 WEIGHT = WIP(NINT-1,M) BEM09270 ELSE BEM09280C BEM09290C Berthod-Zaborwiski quad.,deg. 3 to 11 (2 to 6 nodes)(NSG>0) BEM09300C BEM09310 ETA =XIS(IP,NINT-1) BEM09320 WEIGHT=WIS(IP,NINT-1) BEM09330 END IFC BEM09340C Modification of ETA, in case of singular integration BEM09350C BEM09360 IF (NSG.NE.0) THEN BEM09370 ETAI=(TWO*IN-NNODE-ONE)/(NNODE-ONE) BEM09380 EP=(ONE+THREE*ETAI-TWO*ETAI*IABS(NSG))*HALF BEM09390 EPSI=TWO*IABS(NSG)-THREE BEM09400 IF (NSG.LT.0) THEN BEM09410C BEM09420C Second regular integration BEM09430C BEM09440 ETA=((ONE-EPSI*ETAI)*ETA+EPSI*(ONE+EPSI*ETAI))*HALF BEM09450 IF (EP.LT.EPS) THEN BEM09460 WEIGHT=ZERO BEM09470 ELSE BEM09480 WEIGHT=WEIGHT*EP*DLOG(EP) BEM09490 END IF BEM09500 ELSE BEM09510C BEM09520C Singular integration BEM09530C BEM09540 ETA=ETAI+EPSI*TWO*EP*ETA BEM09550 WEIGHT=-WEIGHT*TWO*EP BEM09560 END IF BEM09570 END IF BEM09580C BEM09590C Shape functions and their derivatives BEM09600C BEM09610 CALL FUNF1(ETA) BEM09620C ---------- BEM09630 CALL DFUNF1(ETA) BEM09640C ----------- BEM09650 CALL D2FUN1(ETA) BEM09660C ----------- BEM09670C BEM09680 RETURN BEM09690C BEM09700 END BEM09710C--------------------------------------------------------------------- BEM09720 SUBROUTINE CARAC1 BEM09730C--------------------------------------------------------------------- BEM09740C0 CARAC1F CARAC1 BEM09750C1 PURPOSE Compute the Xip,Zip,Znx,Znz and Ds at the integration BEM09760C1 point IP of the element IE BEM09770C2 CALL CALL CARAC1 BEM09780C3 CALL ARG. NODE(NNODE) = Nodes of element IE BEM09790C3 XLOC(NNODE) = X-coordinates of element IE nodes BEM09800

    13

  • C3 ZLOC(NNODE) = Z-coordinates of element IE nodes BEM09810C3 FI(NNODE) = Shape functions and ) At point BEM09820C3 DFI(NNODE),D2FI() = their derivatives ) IP BEM09830C3 XIP,ZIP = Current integr. point coordinates BEM09840C3 ZNX,ZNZ = Current integr. point normal vector BEM09850C3 DS = Current integr. point jacobian BEM09860C4 RET. ARG. XIP,ZIP,DS,ZNX,ZNZ BEM09870C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM09880CLCARAC1 SUB. WHICH COMPUTES CARACTERISTICS AT IP OF IE FOR THE 2D-BEM BEM09890C-----------------------------------------------------------------------BEM09900C BEM09910 IMPLICIT REAL*8(A-H,O-Z) BEM09920C BEM09930 PARAMETER (NNODMP=4) BEM09940C 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 BEM09980C BEM09990 DATA ZERO/0.D0/ BEM10000C 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) BEM10120C BEM10130C Dextrorsum Boundary OXZ for the outwards normal vector BEM10140C BEM10150 ZNX=-DZETA/DS BEM10160 ZNZ= DXETA/DS BEM10170C BEM10180C Will serve later, to compute pressure forces BEM10190C BEM10200C COSDS(1)=DXETA BEM10210C COSDS(2)=DZETA BEM10220C COSDS(3)=DXETA*XIP-DZETA*ZIP BEM10230C BEM10240 RETURN BEM10250C BEM10260 END BEM10270C-----------------------------------------------------------------------BEM10280 SUBROUTINE SGDUDN (ZINT,CINT) BEM10290C-----------------------------------------------------------------------BEM10300C0 SGDUDNF SGDUDN BEM10310C1 PURPOSE Compute the local particular integration over IE, for BEM10320C1 du*/dn for the 2D-BEM(0 if straight-line element) BEM10330C2 CALL CALL SGDUDN(ZINT,CINT) BEM10340C3 CALL ARG. NINTR = Nb. of reg. int. pts of IE BEM10350C3 ZINT(,),CINT(NNODE) = Local particular integrals on IE BEM10360C3 IP = current integration point of IE BEM10370C3 XLOC(NNODE) = X-coordinates of element IE nodes BEM10380C3 ZLOC(NNODE) = Z-coordinates of element IE nodes BEM10390C3 FI(NNODE) = Shape functions and ) At point BEM10400C3 DFI(NNODE) = their derivatives ) IP BEM10410C3 WEIGHT = current integr. point integr. weightBEM10420C3 DS = Current integr. point jacobian BEM10430C4 RET. ARG. ZINT,CINT BEM10440C6 INT.CALL FUNC1D,ATANV BEM10450C9 94 S. GRILLI, Ocean Engng., Univ. of Rhode Island BEM10460CLSGDUDN SUB. WHICH COMPUTES THE PARTICULAR INTEG. OF IE FOR THE 2D-BEM BEM10470C-----------------------------------------------------------------------BEM10480C BEM10490 IMPLICIT REAL*8 (A-H,O-Z) BEM10500C BEM10510 PARAMETER (NNODMP=4) BEM10520C 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), BEM10570 . WEIGHT,DS,IP BEM10580C BEM10590 DATA ZERO/0.D0/,EPS/1.D-06/,ONE/1.D0/, BEM10600 . PII2/.1591549430918953D0/ BEM10610C BEM10620C Check if nodes are on line BEM10630C BEM10640 A1=ZLOC(1)-ZLOC(NNODE) BEM10650 B1=XLOC(NNODE)-XLOC(1) BEM10660 C1=XLOC(1)*ZLOC(NNODE)-ZLOC(1)*XLOC(NNODE) BEM10670 M=0 BEM10680 DO I=2,NNODE-1 BEM10690 X1=A1*XLOC(I)+B1*ZLOC(I)+C1 BEM10700 IF (DABS(X1).GT.EPS) M=1 BEM10710 END DO BEM10720 IF (M.EQ.0) THEN BEM10730 CM=ZERO BEM10740 ELSE BEM10750C BEM10760C Check if element steepness is > < 45 degrees BEM10770C BEM10780 IF (DABS(B1).GE.EPS) THEN BEM10790 CFAG=DABS(A1/B1) BEM10800 IF (CFAG.LE.ONE) THEN BEM10810 NFINT=1 BEM10820 END IF BEM10830 ELSE BEM10840 NFINT=-1 BEM10850 END IF BEM10860C BEM10870C Integration BEM10880C BEM10890 DO I=1,NNODE BEM10900 XI=XLOC(I) BEM10910 ZI=ZLOC(I) BEM10920C BEM10930C Constant part BEM10940C BEM10950 ZINT(I,1)=-ATANV (XI,ZI,-ONE,NFINT) BEM10960C ----- BEM10970 DO K=2,NNODE-1 BEM10980 ZINT(I,K)=ZERO BEM10990 END DO BEM11000 ZINT(I,NNODE)=ATANV (XI,ZI,ONE,NFINT) BEM11010C ----- BEM11020 CINT(I)=ZINT(I,1)-ZINT(I,NNODE) BEM11030C BEM11040C Integral part BEM11050C BEM11060 DO IP=1,NINTR BEM11070 CALL FUNC1D (0,0,ETA) BEM11080C ----------- BEM11090 AV=ATANV(XI,ZI,ETA,NFINT) BEM11100C ----- BEM11110 DO J=1,NNODE BEM11120 ZINT(I,J)=ZINT(I,J)-WEIGHT*DFI(J)*AV BEM11130 END DO BEM11140 END DO BEM11150 END DO BEM11160 CM=ONE BEM11170 END IF BEM11180C BEM11190 DO I=1,NNODE BEM11200 CINT(I)=CINT(I)*CM*PII2*NFINT BEM11210 DO J=1,NNODE BEM11220 ZINT(I,J)=ZINT(I,J)*CM*PII2*NFINT BEM11230 END DO BEM11240 END D