1!-------------------------------------------------------------------------------
2
3! This file is part of Code_Saturne, a general-purpose CFD tool.
4!
5! Copyright (C) 1998-2021 EDF S.A.
6!
7! This program is free software; you can redistribute it and/or modify it under
8! the terms of the GNU General Public License as published by the Free Software
9! Foundation; either version 2 of the License, or (at your option) any later
10! version.
11!
12! This program is distributed in the hope that it will be useful, but WITHOUT
13! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
14! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
15! details.
16!
17! You should have received a copy of the GNU General Public License along with
18! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
19! Street, Fifth Floor, Boston, MA 02110-1301, USA.
20
21!-------------------------------------------------------------------------------
22
23!> \file cscfbr.f90
24!> \brief Exchange of variables for coupling two Code_Saturne intances
25!> with boundary faces.
26!>
27!------------------------------------------------------------------------------
28
29!------------------------------------------------------------------------------
30! Arguments
31!------------------------------------------------------------------------------
32!   mode          name          role
33!------------------------------------------------------------------------------
34!> \param[in]     nscal         total number of scalars
35!> \param[in]     icodcl        face boundary condition code:
36!>                               - 1 Dirichlet
37!>                               - 2 Radiative outlet
38!>                               - 3 Neumann
39!>                               - 4 sliding and
40!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
41!>                               - 5 smooth wall and
42!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
43!>                               - 6 rough wall and
44!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
45!>                               - 9 free inlet/outlet
46!>                                 (input mass flux blocked to 0)
47!>                               - 13 Dirichlet for the advection operator and
48!>                                    Neumann for the diffusion operator
49!> \param[in]     itypfb        boundary face types
50!> \param[in]     dt            time step (per cell)
51!> \param[in]     rcodcl        boundary condition values:
52!>                               - rcodcl(1) value of the dirichlet
53!>                               - rcodcl(2) value of the exterior exchange
54!>                                 coefficient (infinite if no exchange)
55!>                               - rcodcl(3) value flux density
56!>                                 (negative if gain) in w/m2 or roughness
57!>                                 in m if icodcl=6
58!>                                 -# for the velocity \f$ (\mu+\mu_T)
59!>                                    \gradv \vect{u} \cdot \vect{n}  \f$
60!>                                 -# for the pressure \f$ \Delta t
61!>                                    \grad P \cdot \vect{n}  \f$
62!>                                 -# for a scalar \f$ cp \left( K +
63!>                                     \dfrac{K_T}{\sigma_T} \right)
64!>                                     \grad T \cdot \vect{n} \f$
65!______________________________________________________________________________
66
67subroutine cscfbr &
68 ( nscal  ,                                                       &
69   icodcl , itypfb ,                                              &
70   dt     ,                                                       &
71   rcodcl )
72
73!===============================================================================
74! Module files
75!===============================================================================
76
77use paramx
78use numvar
79use entsor
80use optcal
81use cstphy
82use cstnum
83use dimens, only: nvar
84use parall
85use period
86use cplsat
87use mesh
88
89!===============================================================================
90
91implicit none
92
93! Arguments
94
95integer          nscal
96
97integer          icodcl(nfabor,nvar)
98integer          itypfb(nfabor)
99
100double precision dt(ncelet)
101double precision rcodcl(nfabor,nvar,3)
102
103! Local variables
104
105integer          numcpl , ivarcp
106integer          ncesup , nfbsup
107integer          ncecpl , nfbcpl , ncencp , nfbncp
108integer          ncedis , nfbdis
109integer          nfbcpg , nfbdig
110integer          ityloc , ityvar
111integer          stride
112
113integer, allocatable, dimension(:) :: lcecpl , lfbcpl , lcencp , lfbncp
114integer, allocatable, dimension(:) :: locpts
115
116double precision, allocatable, dimension(:,:) :: coopts , djppts , dofpts
117double precision, allocatable, dimension(:,:) :: dofcpl
118double precision, allocatable, dimension(:) :: pndpts
119double precision, allocatable, dimension(:) :: pndcpl
120double precision, allocatable, dimension(:,:) :: rvdis , rvfbr
121
122!===============================================================================
123
124
125do numcpl = 1, nbrcpl
126
127!===============================================================================
128! 1.  DEFINITION DE CHAQUE COUPLAGE
129!===============================================================================
130
131  call nbecpl                                                     &
132  !==========
133 ( numcpl ,                                                       &
134   ncesup , nfbsup ,                                              &
135   ncecpl , nfbcpl , ncencp , nfbncp )
136
137  ! Allocate temporary arrays for coupling information
138  allocate(lcecpl(ncecpl), lcencp(ncencp))
139  allocate(lfbcpl(nfbcpl), lfbncp(nfbncp))
140
141!       Liste des cellules et faces de bord localis�es
142  call lelcpl                                                     &
143  !==========
144 ( numcpl ,                                                       &
145   ncecpl , nfbcpl ,                                              &
146   lcecpl , lfbcpl )
147
148!       Liste des cellules et faces de bord non localis�es
149  call lencpl                                                     &
150  !==========
151 ( numcpl ,                                                       &
152   ncencp , nfbncp ,                                              &
153   lcencp , lfbncp )
154
155  ! Free memory
156  deallocate(lcecpl, lcencp)
157
158!===============================================================================
159! 2.  PREPARATION DES VARIABLES A ENVOYER SUR LES FACES DE BORD
160!===============================================================================
161
162  ityvar = 2
163
164! --- Informations g�om�triques de localisation
165
166  call npdcpl(numcpl, ncedis, nfbdis)
167  !==========
168
169  ! Allocate temporary arrays for geometric quantities
170  allocate(locpts(nfbdis))
171  allocate(coopts(3,nfbdis), djppts(3,nfbdis), dofpts(3,nfbdis))
172  allocate(pndpts(nfbdis))
173
174  ! Allocate temporary arrays for variables exchange
175  if (nfbdis.gt.0) then
176    allocate(rvdis(nfbdis,nvarto(numcpl)))
177  else
178    allocate(rvdis(1,nvarto(numcpl)))
179  endif
180  if (nfbcpl.gt.0) then
181    allocate(rvfbr(nfbcpl,nvarto(numcpl)))
182  else
183    allocate(rvfbr(1,nvarto(numcpl)))
184  endif
185
186  call coocpl &
187  !==========
188( numcpl , nfbdis , ityvar , &
189  ityloc , locpts , coopts , &
190  djppts , dofpts , pndpts )
191
192  if (ityloc.eq.2) then
193    write(nfecra,1000)
194    call csexit(1)
195    !==========
196  endif
197
198!       On v�rifie qu'il faut bien �changer quelque chose
199!       de mani�re globale (� cause des appels � GRDCEL notamment)
200  nfbcpg = nfbcpl
201  nfbdig = nfbdis
202  if (irangp.ge.0) then
203    call parcpt(nfbcpg)
204    !==========
205    call parcpt(nfbdig)
206    !==========
207  endif
208
209
210! --- Transfert des variables proprement dit.
211
212  if (nfbdig.gt.0) then
213
214    call cscpfb                                                   &
215    !==========
216  ( nscal  ,                                                      &
217    nfbdis , numcpl , nvarto(numcpl) ,                            &
218    locpts ,                                                      &
219    coopts , djppts , pndpts ,                                    &
220    rvdis  , dofpts )
221
222  endif
223
224  ! Free memory
225  deallocate(locpts)
226  deallocate(coopts, djppts, dofpts)
227  deallocate(pndpts)
228
229!       Cet appel est sym�trique, donc on teste sur NFBDIG et NFBCPG
230!       (rien a envoyer, rien a recevoir)
231  if (nfbdig.gt.0.or.nfbcpg.gt.0) then
232
233    do ivarcp = 1, nvarto(numcpl)
234
235      stride = 1
236
237      call varcpl &
238      !==========
239    ( numcpl , nfbdis , nfbcpl , ityvar , stride , &
240      rvdis(1, ivarcp) ,                           &
241      rvfbr(1, ivarcp) )
242
243    enddo
244
245  endif
246
247  ! Free memory
248  deallocate(rvdis)
249
250!===============================================================================
251! 3.  TRADUCTION DU COUPLAGE EN TERME DE CONDITIONS AUX LIMITES
252!===============================================================================
253
254  if (nfbcpg.gt.0) then
255
256    ! Allocate temporary arrays for geometric quantities
257    allocate(dofcpl(3,nfbcpl))
258    allocate(pndcpl(nfbcpl))
259
260    call pondcp &
261    !==========
262  ( numcpl , nfbcpl , ityvar , pndcpl , dofcpl )
263
264    call csc2cl &
265    !==========
266  ( nvarcp(numcpl), nvarto(numcpl) , nfbcpl , nfbncp ,            &
267    icodcl , itypfb ,                                             &
268    lfbcpl , lfbncp ,                                             &
269    dt     ,                                                      &
270    rcodcl ,                                                      &
271    rvfbr  , pndcpl , dofcpl )
272
273    ! Free memory
274    deallocate(dofcpl, pndcpl)
275
276  endif
277
278  ! Free memory
279  deallocate(rvfbr)
280  deallocate(lfbcpl, lfbncp)
281
282enddo
283!     Fin de la boucle sur les couplages
284
285
286!--------
287! FORMATS
288!--------
289 1000 format(                                                           &
290'@                                                            ',/,&
291'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
292'@                                                            ',/,&
293'@ @@ ATTENTION :                                             ',/,&
294'@    =========                                               ',/,&
295'@    LE COUPLAGE VIA LES FACES EN TANT QU''ELEMENTS          ',/,&
296'@    SUPPORTS N''EST PAS ENCORE GERE PAR LE NOYAU.           ',/,&
297'@                                                            ',/,&
298'@  Le calcul ne peut etre execute.                           ',/,&
299'@                                                            ',/,&
300'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
301'@                                                            ',/)
302!----
303! FIN
304!----
305
306return
307end subroutine
308
309!===============================================================================
310
311!> \brief Initialization for coupling two Code_Saturne intances
312!>        with boundary faces.
313!>
314!------------------------------------------------------------------------------
315
316!------------------------------------------------------------------------------
317! Arguments
318!------------------------------------------------------------------------------
319!   mode          name          role
320!------------------------------------------------------------------------------
321!> \param[in]     icodcl        face boundary condition code:
322!>                               - 1 Dirichlet
323!>                               - 2 Radiative outlet
324!>                               - 3 Neumann
325!>                               - 4 sliding and
326!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
327!>                               - 5 smooth wall and
328!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
329!>                               - 6 rough wall and
330!>                                 \f$ \vect{u} \cdot \vect{n} = 0 \f$
331!>                               - 9 free inlet/outlet
332!>                                 (input mass flux blocked to 0)
333!>                               - 13 Dirichlet for the advection operator and
334!>                                    Neumann for the diffusion operator
335!> \param[in]     itypfb        boundary face types
336!______________________________________________________________________________
337
338subroutine cscfbr_init(icodcl, itypfb)
339
340!===============================================================================
341! Module files
342!===============================================================================
343
344use paramx
345use numvar
346use entsor
347use optcal
348use cstphy
349use cstnum
350use dimens, only: nvar
351use parall
352use period
353use cplsat
354use mesh
355
356!===============================================================================
357
358implicit none
359
360! Arguments
361
362integer          icodcl(nfabor,nvar)
363integer          itypfb(nfabor)
364
365! Local variables
366
367integer          numcpl
368integer          ncesup , nfbsup
369integer          ncecpl , nfbcpl , ncencp , nfbncp
370
371integer, allocatable, dimension(:) :: lcecpl , lfbcpl , lcencp , lfbncp
372
373!===============================================================================
374
375
376do numcpl = 1, nbrcpl
377
378  ! For each coupling
379
380  call nbecpl(numcpl, ncesup, nfbsup,                            &
381              ncecpl, nfbcpl, ncencp, nfbncp)
382
383  ! Allocate temporary arrays for coupling information
384  allocate(lcecpl(ncecpl), lcencp(ncencp))
385  allocate(lfbcpl(nfbcpl), lfbncp(nfbncp))
386
387  ! Located cells and boundary faces
388  call lelcpl(numcpl, ncecpl, nfbcpl, lcecpl, lfbcpl)
389
390  ! Unlocated cells and boundary faces
391  call lencpl(numcpl, ncencp, nfbncp, lcencp, lfbncp)
392
393  ! Free memory
394  deallocate(lcecpl, lcencp)
395
396!===============================================================================
397! 2.  TRADUCTION DU COUPLAGE EN TERME DE CONDITIONS AUX LIMITES
398!===============================================================================
399
400  if (nfbcpl.gt.0) then
401    call csc2cl_init(nvarcp(numcpl), nfbcpl, nfbncp,              &
402                     icodcl, itypfb, lfbcpl, lfbncp)
403  endif
404
405  ! Free memory
406  deallocate(lfbcpl, lfbncp)
407
408enddo
409
410return
411end subroutine cscfbr_init
412