The TELEMAC-MASCARET system  trunk
share_3d_fluxes.f
Go to the documentation of this file.
1 ! **************************
2  SUBROUTINE share_3d_fluxes
3 ! **************************
4 !
5  &(flux,nplan,mesh2,mesh3,opt)
6 !
7 !***********************************************************************
8 ! BIEF V7P1
9 !***********************************************************************
10 !
11 !brief Shares assembled fluxes between sub-domains.
12 !+ Only one sub-domain will receive the whole flux to be treated.
13 !
14 !warning MUST NOT BE CALLED WHEN NCSIZE = 0
15 !
16 !history J-M HERVOUET (LNHE)
17 !+ 14/04/2010
18 !+ V6P0
19 !+ First version
20 !
21 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
22 !+ 13/07/2010
23 !+ V6P0
24 !+ Translation of French comments within the FORTRAN sources into
25 !+ English comments
26 !
27 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
28 !+ 21/08/2010
29 !+ V6P0
30 !+ Creation of DOXYGEN tags for automated documentation and
31 !+ cross-referencing of the FORTRAN sources
32 !
33 !history J-M HERVOUET (EDF LAB, LNHE)
34 !+ 12/06/2015
35 !+ V7P1
36 !+ The fluxes are no longer shared but given to a single processor.
37 !
38 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
39 !| FLUX |<->| FLUXES TO BE SHARED
40 !| MESH2 |-->| 2D MESH
41 !| MESH3 |-->| 3D MESH
42 !| NPLAN |-->| NUMBER OF PLANES
43 !| OPT |-->| 1 : HORIZONTAL AND VERTICAL SEGMENTS ONLY
44 !| | | 2 : ALL SEGMENTS
45 !| XMUL |-->| MULTIPLICATING FACTOR
46 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
47 !
48  USE bief, ex_share_3d_fluxes => share_3d_fluxes
49 !
51  IMPLICIT NONE
52 !
53 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
54 !
55  INTEGER, INTENT(IN) :: NPLAN,OPT
56 !
57  TYPE(bief_mesh) , INTENT(INOUT) :: MESH2,MESH3
58 !
59  DOUBLE PRECISION, INTENT(INOUT) :: FLUX(*)
60 !
61 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
62 !
63  INTEGER IPLAN,NSEG,NSEGH,NSEGV,NPOIN2,I,I3D,I2D,IAD
64 !
65 !-----------------------------------------------------------------------
66 !
67  nseg=mesh2%NSEG
68  npoin2=mesh2%NPOIN
69  nsegh=nseg*nplan
70  nsegv=npoin2*(nplan-1)
71 !
72 ! HORIZONTAL FLUXES
73 !
74  DO iplan=1,nplan
75  CALL mult_interface_seg(flux(1+(iplan-1)*nseg:iplan*nseg),
76  & mesh2%NH_COM_SEG%I,
77  & mesh2%NH_COM_SEG%DIM1,
78  & mesh2%NB_NEIGHB_SEG,
79  & mesh2%NB_NEIGHB_PT_SEG%I,
80  & mesh2%LIST_SEND_SEG%I,mesh2%NSEG)
81  ENDDO
82 !
83 ! VERTICAL FLUXES (SAME NUMBERING AS POINTS, SO FAC%R(I))
84 !
85  iad=1
86  DO i=1,nptir
87 ! I2D=NACHB(1,I) WITH NACHB OF SIZE NACHB(NBMAXNSHARE,NPTIR)
88 ! IAD IS (I-1)*NBMAXNSHARE+1
89  i2d=mesh2%NACHB%I(iad)
90  DO iplan=1,nplan-1
91  i3d=(iplan-1)*npoin2+i2d
92  flux(nsegh+i3d)=flux(nsegh+i3d)*mesh3%IFAC%I(i3d)
93  ENDDO
94  iad=iad+nbmaxnshare
95  ENDDO
96 !
97 ! CROSSED FLUXES (SEE STOSEG41 FOR STORAGE). THERE ARE 2*NESG
98 ! PER LAYER AND NPLAN-1 LAYER. HERE ORISEG=1 AND ORISEG=2 SEGMENTS
99 ! ARE MULTIPLIED BY THE SAME NUMBER, SO GIVEN HOW THE NUMBERING
100 ! IS BUILT IT IS AS IF WE HAVE 2*NPLAN-2 LAYERS OF HORIZONTAL SEGMENTS
101 !
102  IF(opt.EQ.2) THEN
103  DO iplan=1,2*(nplan-1)
104  CALL mult_interface_seg(flux(1+nsegh+nsegv+(iplan-1)*nseg:
105  & nsegh+nsegv+ iplan *nseg),
106  & mesh2%NH_COM_SEG%I,
107  & mesh2%NH_COM_SEG%DIM1,
108  & mesh2%NB_NEIGHB_SEG,
109  & mesh2%NB_NEIGHB_PT_SEG%I,
110  & mesh2%LIST_SEND_SEG%I,mesh2%NSEG)
111  ENDDO
112  ENDIF
113 !
114 !-----------------------------------------------------------------------
115 !
116  RETURN
117  END
118 
subroutine mult_interface_seg(FSEG, NH_COM_SEG, DIM1NHCOM, NB_NEIGHB_SEG, NB_NEIGHB_PT_SEG, LIST_SEND, NSEG)
subroutine share_3d_fluxes(FLUX, NPLAN, MESH2, MESH3, OPT)
Definition: bief.f:3