The TELEMAC-MASCARET system  trunk
flux3dlim.f
Go to the documentation of this file.
1 ! ********************
2  SUBROUTINE flux3dlim
3 ! ********************
4 !
5  &(flow,flulim,nplan,nseg2d,npoin2,opt)
6 !
7 !***********************************************************************
8 ! BIEF V6P3 21/08/2010
9 !***********************************************************************
10 !
11 !brief LIMITS 3D HORIZONTAL EDGE BY EDGE FLUXES ON POINTS.
12 !
13 !history J-M HERVOUET (LNHE)
14 !+ 19/05/09
15 !+ V6P0
16 !+
17 !
18 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
19 !+ 13/07/2010
20 !+ V6P0
21 !+ Translation of French comments within the FORTRAN sources into
22 !+ English comments
23 !
24 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
25 !+ 21/08/2010
26 !+ V6P0
27 !+ Creation of DOXYGEN tags for automated documentation and
28 !+ cross-referencing of the FORTRAN sources
29 !
30 !history J-M HERVOUET (LNHE)
31 !+ 06/09/2012
32 !+ V6P2
33 !+ Option OPT added for crossed segments. Argument NPOIN2 added.
34 !+ Prisms and prisms cut into tetrahedra now treated.
35 !
36 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
37 !| FLOW |-->| FLUXES (SIZE OF FLOW MAY NOT EXCEED
38 !| | | NSEG2D*NPLAN, THOUGH THE TOTAL NUMBER OF
39 !| | | SEGMENTS IS LARGER)
40 !| FLULIM |-->| LIMITING FACTOR OF 2D SEGMENTS
41 !| NPLAN |-->| NUMBER OF PLANES
42 !| NPOIN2 |-->| NUMBER OF POINTS IN 2D
43 !| NSEG2D |-->| NUMBER OF SEGMENTS IN 2D
44 !| OPT |-->| 1: HORIZONTAL SEGMENTS
45 !| | | 2: HORIZONTAL AND CROSSED SEGMENTS FOR PRISMS
46 !| | | 3: HORIZONTAL AND CROSSED SEGMENTS FOR PRISMS
47 !| | | CUT INTO TETRAHEDRA
48 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
49 !
50  USE bief
51 !
53  IMPLICIT NONE
54 !
55 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
56 !
57  INTEGER, INTENT(IN) :: NSEG2D,NPLAN,OPT,NPOIN2
58  DOUBLE PRECISION, INTENT(INOUT) :: FLOW(*)
59 ! HERE * = NESG2D*NPLAN
60  DOUBLE PRECISION, INTENT(IN) :: FLULIM(nseg2d)
61 !
62 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
63 !
64  INTEGER ISEG,ISEG3D,IPLAN,OTHERS
65 !
66 !-----------------------------------------------------------------------
67 !
68 ! LIMITS 3D FLUXES BY COEFFICIENT OF 2D FLUXES
69 !
70 !-----------------------------------------------------------------------
71 !
72 ! HORIZONTAL SEGMENTS
73 !
74  DO iplan=1,nplan
75  DO iseg=1,nseg2d
76  iseg3d=iseg+(iplan-1)*nseg2d
77  flow(iseg3d)=flow(iseg3d)*flulim(iseg)
78  ENDDO
79  ENDDO
80 !
81 ! OPTIONALLY: CROSSED SEGMENTS
82 !
83  IF(opt.EQ.2) THEN
84 !
85 ! FOR PRISMS
86 !
87  others=nplan*nseg2d+npoin2*(nplan-1)
88  DO iplan=1,nplan-1
89  DO iseg=1,nseg2d
90  iseg3d=iseg+(iplan-1)*2*nseg2d+others
91  flow(iseg3d)=flow(iseg3d)*flulim(iseg)
92  iseg3d=iseg3d+nseg2d
93  flow(iseg3d)=flow(iseg3d)*flulim(iseg)
94  ENDDO
95  ENDDO
96 !
97  ELSEIF(opt.EQ.3) THEN
98 !
99 ! FOR PRISMS CUT INTO TETRAHEDRA
100 !
101  others=nplan*nseg2d+npoin2*(nplan-1)
102  DO iplan=1,nplan-1
103  DO iseg=1,nseg2d
104  iseg3d=iseg+(iplan-1)*nseg2d+others
105  flow(iseg3d)=flow(iseg3d)*flulim(iseg)
106  ENDDO
107  ENDDO
108 !
109  ELSEIF(opt.NE.1) THEN
110 !
111  WRITE(lu,*) 'FLUX3DLIM : UNEXPECTED OPT:',opt
112  CALL plante(1)
113  stop
114 !
115  ENDIF
116 !
117 !-----------------------------------------------------------------------
118 !
119  RETURN
120  END
subroutine flux3dlim(FLOW, FLULIM, NPLAN, NSEG2D, NPOIN2, OPT)
Definition: flux3dlim.f:7
Definition: bief.f:3