source: palm/trunk/SOURCE/surface_coupler.f90 @ 2001

Last change on this file since 2001 was 2001, checked in by knoop, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 22.5 KB
RevLine 
[1682]1!> @file surface_coupler.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1036]9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[1818]17! Copyright 1997-2016 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[258]20! Current revisions:
[1092]21! ------------------
[1321]22!
[2001]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: surface_coupler.f90 2001 2016-08-20 18:41:22Z knoop $
27!
[2001]28! 2000 2016-08-20 18:09:15Z knoop
29! Forced header and separation lines into 80 columns
30!
[1683]31! 1682 2015-10-07 23:56:08Z knoop
32! Code annotations made doxygen readable
33!
[1428]34! 1427 2014-07-07 14:04:59Z maronga
35! Bugfix: value of l_v corrected.
36!
[1419]37! 1418 2014-06-06 13:05:08Z fricke
38! Bugfix: For caluclation of the salinity flux at the sea surface,
39!          the given value for salinity must be in percent and not in psu
40!
[1354]41! 1353 2014-04-08 15:21:23Z heinze
42! REAL constants provided with KIND-attribute
43!
[1325]44! 1324 2014-03-21 09:13:16Z suehring
45! Bugfix: ONLY statement for module pegrid removed
46!
[1323]47! 1322 2014-03-20 16:38:49Z raasch
48! REAL constants defined as wp-kind
49!
[1321]50! 1320 2014-03-20 08:40:49Z raasch
[1320]51! ONLY-attribute added to USE-statements,
52! kind-parameters added to all INTEGER and REAL declaration statements,
53! kinds are defined in new module kinds,
54! old module precision_kind is removed,
55! revision history before 2012 removed,
56! comment fields (!:) to be used for variable explanations added to
57! all variable declaration statements
[102]58!
[1319]59! 1318 2014-03-17 13:35:16Z raasch
60! module interfaces removed
61!
[1093]62! 1092 2013-02-02 11:24:22Z raasch
63! unused variables removed
64!
[1037]65! 1036 2012-10-22 13:43:42Z raasch
66! code put under GPL (PALM 3.9)
67!
[881]68! 880 2012-04-13 06:28:59Z raasch
69! Bugfix: preprocessor statements for parallel execution added
70!
[110]71! 109 2007-08-28 15:26:47Z letzel
[102]72! Initial revision
73!
74! Description:
75! ------------
[1682]76!> Data exchange at the interface between coupled models
[102]77!------------------------------------------------------------------------------!
[1682]78 SUBROUTINE surface_coupler
79 
[102]80
[1320]81    USE arrays_3d,                                                             &
82        ONLY:  pt, shf, qsws, qswst_remote, rho, sa, saswst, total_2d_a,       &
83               total_2d_o, tswst, u, usws, uswst, v, vsws, vswst
84
[1427]85    USE cloud_parameters,                                                      &
86        ONLY:  cp, l_v
87
[1320]88    USE control_parameters,                                                    &
89        ONLY:  coupling_mode, coupling_mode_remote, coupling_topology,         &
90               humidity, humidity_remote, message_string, terminate_coupled,   &
91               terminate_coupled_remote, time_since_reference_point
92
93    USE cpulog,                                                                &
94        ONLY:  cpu_log, log_point
95
96    USE indices,                                                               &
97        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_a, nx_o, ny, nyn, nyng, nys, &
98               nysg, ny_a, ny_o, nzt
99
100    USE kinds
101
[102]102    USE pegrid
103
104    IMPLICIT NONE
105
[1682]106    REAL(wp)    ::  time_since_reference_point_rem        !<
107    REAL(wp)    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp) !<
[102]108
[1682]109    REAL(wp)    ::  cpw = 4218.0_wp !< heat capacity of water at constant pressure
[1427]110
[206]111#if defined( __parallel )
[102]112
[667]113    CALL cpu_log( log_point(39), 'surface_coupler', 'start' )
[102]114
[667]115
116
[102]117!
[108]118!-- In case of model termination initiated by the remote model
119!-- (terminate_coupled_remote > 0), initiate termination of the local model.
120!-- The rest of the coupler must then be skipped because it would cause an MPI
121!-- intercomminucation hang.
122!-- If necessary, the coupler will be called at the beginning of the next
123!-- restart run.
[667]124
125    IF ( coupling_topology == 0 ) THEN
[709]126       CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER, target_id, &
127                          0,                                                   &
128                          terminate_coupled_remote, 1, MPI_INTEGER, target_id, &
[667]129                          0, comm_inter, status, ierr )
130    ELSE
131       IF ( myid == 0) THEN
132          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER, &
133                             target_id, 0,                             &
134                             terminate_coupled_remote, 1, MPI_INTEGER, & 
135                             target_id, 0,                             &
136                             comm_inter, status, ierr )
137       ENDIF
[709]138       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, &
139                       ierr )
[667]140
141       ALLOCATE( total_2d_a(-nbgp:ny_a+nbgp,-nbgp:nx_a+nbgp),       &
142                 total_2d_o(-nbgp:ny_o+nbgp,-nbgp:nx_o+nbgp) )
143
144    ENDIF
145
[108]146    IF ( terminate_coupled_remote > 0 )  THEN
[274]147       WRITE( message_string, * ) 'remote model "',                         &
148                                  TRIM( coupling_mode_remote ),             &
149                                  '" terminated',                           &
150                                  '&with terminate_coupled_remote = ',      &
151                                  terminate_coupled_remote,                 &
152                                  '&local model  "', TRIM( coupling_mode ), &
153                                  '" has',                                  &
154                                  '&terminate_coupled = ',                  &
[667]155                                   terminate_coupled
[258]156       CALL message( 'surface_coupler', 'PA0310', 1, 2, 0, 6, 0 )
[108]157       RETURN
158    ENDIF
[667]159 
[291]160
[108]161!
162!-- Exchange the current simulated time between the models,
[667]163!-- currently just for total_2ding
[709]164    IF ( coupling_topology == 0 ) THEN
165   
166       CALL MPI_SEND( time_since_reference_point, 1, MPI_REAL, target_id, 11, &
167                      comm_inter, ierr )
168       CALL MPI_RECV( time_since_reference_point_rem, 1, MPI_REAL, target_id, &
169                      11, comm_inter, status, ierr )
[667]170    ELSE
[709]171
[667]172       IF ( myid == 0 ) THEN
[709]173
174          CALL MPI_SEND( time_since_reference_point, 1, MPI_REAL, target_id, &
175                         11, comm_inter, ierr )
176          CALL MPI_RECV( time_since_reference_point_rem, 1, MPI_REAL,        &
[667]177                         target_id, 11, comm_inter, status, ierr )
[709]178
[667]179       ENDIF
[709]180
181       CALL MPI_BCAST( time_since_reference_point_rem, 1, MPI_REAL, 0, comm2d, &
182                       ierr )
183
[667]184    ENDIF
[102]185
186!
187!-- Exchange the interface data
188    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
[667]189   
190!
[709]191!--    Horizontal grid size and number of processors is equal in ocean and
192!--    atmosphere
193       IF ( coupling_topology == 0 )  THEN
[102]194
195!
[709]196!--       Send heat flux at bottom surface to the ocean
197          CALL MPI_SEND( shf(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 12, &
198                         comm_inter, ierr )
[102]199!
[709]200!--       Send humidity flux at bottom surface to the ocean
[667]201          IF ( humidity )  THEN
[709]202             CALL MPI_SEND( qsws(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 13, &
203                            comm_inter, ierr )
[667]204          ENDIF
205!
[709]206!--       Receive temperature at the bottom surface from the ocean
207          CALL MPI_RECV( pt(0,nysg,nxlg), 1, type_xy, target_id, 14, &
208                         comm_inter, status, ierr )
[108]209!
[709]210!--       Send the momentum flux (u) at bottom surface to the ocean
211          CALL MPI_SEND( usws(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 15, &
212                         comm_inter, ierr )
[102]213!
[709]214!--       Send the momentum flux (v) at bottom surface to the ocean
215          CALL MPI_SEND( vsws(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 16, &
216                         comm_inter, ierr )
[102]217!
[709]218!--       Receive u at the bottom surface from the ocean
219          CALL MPI_RECV( u(0,nysg,nxlg), 1, type_xy, target_id, 17, &
220                         comm_inter, status, ierr )
[667]221!
[709]222!--       Receive v at the bottom surface from the ocean
223          CALL MPI_RECV( v(0,nysg,nxlg), 1, type_xy, target_id, 18, &
224                         comm_inter, status, ierr )
[667]225!
226!--    Horizontal grid size or number of processors differs between
227!--    ocean and atmosphere
228       ELSE
229     
230!
[709]231!--       Send heat flux at bottom surface to the ocean
[1353]232          total_2d_a = 0.0_wp
233          total_2d   = 0.0_wp
[667]234          total_2d(nys:nyn,nxl:nxr) = shf(nys:nyn,nxl:nxr)
[709]235
236          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0, &
237                           comm2d, ierr )
238          CALL interpolate_to_ocean( 12 )   
[667]239!
[709]240!--       Send humidity flux at bottom surface to the ocean
241          IF ( humidity )  THEN
[1353]242             total_2d_a = 0.0_wp
243             total_2d   = 0.0_wp
[667]244             total_2d(nys:nyn,nxl:nxr) = qsws(nys:nyn,nxl:nxr)
[709]245
246             CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, &
247                              0, comm2d, ierr )
248             CALL interpolate_to_ocean( 13 )
[667]249          ENDIF
250!
[709]251!--       Receive temperature at the bottom surface from the ocean
252          IF ( myid == 0 )  THEN
[667]253             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, &
254                            target_id, 14, comm_inter, status, ierr )   
255          ENDIF
256          CALL MPI_BARRIER( comm2d, ierr )
[709]257          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
258                          ierr )
[667]259          pt(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
260!
[709]261!--       Send momentum flux (u) at bottom surface to the ocean
[1353]262          total_2d_a = 0.0_wp 
263          total_2d   = 0.0_wp
[667]264          total_2d(nys:nyn,nxl:nxr) = usws(nys:nyn,nxl:nxr)
[709]265          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0, &
266                           comm2d, ierr )
267          CALL interpolate_to_ocean( 15 )
[667]268!
[709]269!--       Send momentum flux (v) at bottom surface to the ocean
[1353]270          total_2d_a = 0.0_wp
271          total_2d   = 0.0_wp
[667]272          total_2d(nys:nyn,nxl:nxr) = vsws(nys:nyn,nxl:nxr)
[709]273          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0, &
274                           comm2d, ierr )
275          CALL interpolate_to_ocean( 16 )
[667]276!
[709]277!--       Receive u at the bottom surface from the ocean
278          IF ( myid == 0 )  THEN
[667]279             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, &
[709]280                            target_id, 17, comm_inter, status, ierr )
[667]281          ENDIF
282          CALL MPI_BARRIER( comm2d, ierr )
[709]283          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
284                          ierr )
[667]285          u(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
286!
[709]287!--       Receive v at the bottom surface from the ocean
288          IF ( myid == 0 )  THEN
[667]289             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, &
[709]290                            target_id, 18, comm_inter, status, ierr )
[667]291          ENDIF
292          CALL MPI_BARRIER( comm2d, ierr )
[709]293          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
294                          ierr )
[667]295          v(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
296
297       ENDIF
298
[102]299    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
300
301!
[667]302!--    Horizontal grid size and number of processors is equal
303!--    in ocean and atmosphere
304       IF ( coupling_topology == 0 ) THEN
305!
[709]306!--       Receive heat flux at the sea surface (top) from the atmosphere
307          CALL MPI_RECV( tswst(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 12, &
308                         comm_inter, status, ierr )
[102]309!
[709]310!--       Receive humidity flux from the atmosphere (bottom)
[667]311!--       and add it to the heat flux at the sea surface (top)...
312          IF ( humidity_remote )  THEN
313             CALL MPI_RECV( qswst_remote(nysg,nxlg), ngp_xy, MPI_REAL, &
314                            target_id, 13, comm_inter, status, ierr )
315          ENDIF
316!
317!--       Send sea surface temperature to the atmosphere model
[709]318          CALL MPI_SEND( pt(nzt,nysg,nxlg), 1, type_xy, target_id, 14, &
319                         comm_inter, ierr )
[667]320!
321!--       Receive momentum flux (u) at the sea surface (top) from the atmosphere
[709]322          CALL MPI_RECV( uswst(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 15, &
323                         comm_inter, status, ierr )
[667]324!
325!--       Receive momentum flux (v) at the sea surface (top) from the atmosphere
[709]326          CALL MPI_RECV( vswst(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 16, &
327                         comm_inter, status, ierr )
[667]328!
[709]329!--       Send u to the atmosphere
330          CALL MPI_SEND( u(nzt,nysg,nxlg), 1, type_xy, target_id, 17, &
331                         comm_inter, ierr )
[667]332!
[709]333!--       Send v to the atmosphere
334          CALL MPI_SEND( v(nzt,nysg,nxlg), 1, type_xy, target_id, 18, &
335                         comm_inter, ierr )
336!
[667]337!--    Horizontal gridsize or number of processors differs between
338!--    ocean and atmosphere
339       ELSE
340!
[709]341!--       Receive heat flux at the sea surface (top) from the atmosphere
342          IF ( myid == 0 )  THEN
[667]343             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]344                            target_id, 12, comm_inter, status, ierr )
[667]345          ENDIF
346          CALL MPI_BARRIER( comm2d, ierr )
[709]347          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, comm2d, &
348                          ierr )
[667]349          tswst(nysg:nyng,nxlg:nxrg) = total_2d_o(nysg:nyng,nxlg:nxrg)
350!
[709]351!--       Receive humidity flux at the sea surface (top) from the atmosphere
352          IF ( humidity_remote )  THEN
353             IF ( myid == 0 )  THEN
[667]354                CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]355                               target_id, 13, comm_inter, status, ierr )
[667]356             ENDIF
357             CALL MPI_BARRIER( comm2d, ierr )
[709]358             CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, &
359                             comm2d, ierr)
[667]360             qswst_remote(nysg:nyng,nxlg:nxrg) = total_2d_o(nysg:nyng,nxlg:nxrg)
361          ENDIF
362!
363!--       Send surface temperature to atmosphere
[1353]364          total_2d_o = 0.0_wp
365          total_2d   = 0.0_wp
[667]366          total_2d(nys:nyn,nxl:nxr) = pt(nzt,nys:nyn,nxl:nxr)
367
[709]368          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
369                           comm2d, ierr) 
370          CALL interpolate_to_atmos( 14 )
[667]371!
[709]372!--       Receive momentum flux (u) at the sea surface (top) from the atmosphere
373          IF ( myid == 0 )  THEN
[667]374             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]375                            target_id, 15, comm_inter, status, ierr )
[667]376          ENDIF
377          CALL MPI_BARRIER( comm2d, ierr )
378          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]379                          0, comm2d, ierr )
[667]380          uswst(nysg:nyng,nxlg:nxrg) = total_2d_o(nysg:nyng,nxlg:nxrg)
381!
[709]382!--       Receive momentum flux (v) at the sea surface (top) from the atmosphere
383          IF ( myid == 0 )  THEN
[667]384             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]385                            target_id, 16, comm_inter, status, ierr )
[667]386          ENDIF
387          CALL MPI_BARRIER( comm2d, ierr )
[709]388          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, comm2d, &
389                          ierr )
[667]390          vswst(nysg:nyng,nxlg:nxrg) = total_2d_o(nysg:nyng,nxlg:nxrg)
391!
392!--       Send u to atmosphere
[1353]393          total_2d_o = 0.0_wp 
394          total_2d   = 0.0_wp
[667]395          total_2d(nys:nyn,nxl:nxr) = u(nzt,nys:nyn,nxl:nxr)
[709]396          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
397                           comm2d, ierr )
398          CALL interpolate_to_atmos( 17 )
[667]399!
400!--       Send v to atmosphere
[1353]401          total_2d_o = 0.0_wp
402          total_2d   = 0.0_wp
[667]403          total_2d(nys:nyn,nxl:nxr) = v(nzt,nys:nyn,nxl:nxr)
[709]404          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
405                           comm2d, ierr )
406          CALL interpolate_to_atmos( 18 )
[667]407       
408       ENDIF
409
410!
411!--    Conversions of fluxes received from atmosphere
412       IF ( humidity_remote )  THEN
[108]413!
[709]414!--       Here tswst is still the sum of atmospheric bottom heat fluxes,
415!--       * latent heat of vaporization in m2/s2, or 540 cal/g, or 40.65 kJ/mol
416!--       /(rho_atm(=1.0)*c_p)
[1427]417          tswst = tswst + qswst_remote * l_v / cp
[709]418!
[667]419!--        ...and convert it to a salinity flux at the sea surface (top)
[108]420!--       following Steinhorn (1991), JPO 21, pp. 1681-1683:
421!--       S'w' = -S * evaporation / ( rho_water * ( 1 - S ) )
[1427]422          saswst = -1.0_wp * sa(nzt,:,:) * 0.001_wp * qswst_remote /  &
423                    ( rho(nzt,:,:) * ( 1.0_wp - sa(nzt,:,:) * 0.001_wp ) )
[108]424       ENDIF
425
426!
[102]427!--    Adjust the kinematic heat flux with respect to ocean density
428!--    (constants are the specific heat capacities for air and water)
[667]429!--    now tswst is the ocean top heat flux
[1427]430       tswst = tswst / rho(nzt,:,:) * cp / cpw
[102]431
432!
[667]433!--    Adjust the momentum fluxes with respect to ocean density
434       uswst = uswst / rho(nzt,:,:)
435       vswst = vswst / rho(nzt,:,:)
[102]436
[667]437    ENDIF
438
[709]439    IF ( coupling_topology == 1 )  THEN
[667]440       DEALLOCATE( total_2d_o, total_2d_a )
441    ENDIF
442
443    CALL cpu_log( log_point(39), 'surface_coupler', 'stop' )
444
445#endif
446
447  END SUBROUTINE surface_coupler
448
449
450
[1682]451!------------------------------------------------------------------------------!
452! Description:
453! ------------
454!> @todo Missing subroutine description.
455!------------------------------------------------------------------------------!
[709]456  SUBROUTINE interpolate_to_atmos( tag )
[667]457
[880]458#if defined( __parallel )
459
[1320]460    USE arrays_3d,                                                             &
461        ONLY:  total_2d_a, total_2d_o
[667]462
[1320]463    USE indices,                                                               &
464        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
465
466    USE kinds
467
[1324]468    USE pegrid
[1320]469
[667]470    IMPLICIT NONE
471
[1682]472    INTEGER(iwp) ::  dnx  !<
473    INTEGER(iwp) ::  dnx2 !<
474    INTEGER(iwp) ::  dny  !<
475    INTEGER(iwp) ::  dny2 !<
476    INTEGER(iwp) ::  i    !<
477    INTEGER(iwp) ::  ii   !<
478    INTEGER(iwp) ::  j    !<
479    INTEGER(iwp) ::  jj   !<
[667]480
[1682]481    INTEGER(iwp), intent(in) ::  tag !<
[1320]482
[667]483    CALL MPI_BARRIER( comm2d, ierr )
484
[709]485    IF ( myid == 0 )  THEN
486!
487!--    Cyclic boundary conditions for the total 2D-grid
[667]488       total_2d_o(-nbgp:-1,:) = total_2d_o(ny+1-nbgp:ny,:)
489       total_2d_o(:,-nbgp:-1) = total_2d_o(:,nx+1-nbgp:nx)
490
491       total_2d_o(ny+1:ny+nbgp,:) = total_2d_o(0:nbgp-1,:)
492       total_2d_o(:,nx+1:nx+nbgp) = total_2d_o(:,0:nbgp-1)
493
[102]494!
[667]495!--    Number of gridpoints of the fine grid within one mesh of the coarse grid
496       dnx = (nx_o+1) / (nx_a+1) 
497       dny = (ny_o+1) / (ny_a+1) 
[102]498
499!
[709]500!--    Distance for interpolation around coarse grid points within the fine
501!--    grid (note: 2*dnx2 must not be equal with dnx)
[667]502       dnx2 = 2 * ( dnx / 2 )
503       dny2 = 2 * ( dny / 2 )
[102]504
[1353]505       total_2d_a = 0.0_wp
[102]506!
[667]507!--    Interpolation from ocean-grid-layer to atmosphere-grid-layer
508       DO  j = 0, ny_a
509          DO  i = 0, nx_a 
510             DO  jj = 0, dny2
511                DO  ii = 0, dnx2
512                   total_2d_a(j,i) = total_2d_a(j,i) &
513                                     + total_2d_o(j*dny+jj,i*dnx+ii)
514                ENDDO
515             ENDDO
516             total_2d_a(j,i) = total_2d_a(j,i) / ( ( dnx2 + 1 ) * ( dny2 + 1 ) )
517          ENDDO
518       ENDDO
519!
[709]520!--    Cyclic boundary conditions for atmosphere grid
[667]521       total_2d_a(-nbgp:-1,:) = total_2d_a(ny_a+1-nbgp:ny_a,:)
522       total_2d_a(:,-nbgp:-1) = total_2d_a(:,nx_a+1-nbgp:nx_a)
523       
524       total_2d_a(ny_a+1:ny_a+nbgp,:) = total_2d_a(0:nbgp-1,:)
525       total_2d_a(:,nx_a+1:nx_a+nbgp) = total_2d_a(:,0:nbgp-1)
526!
527!--    Transfer of the atmosphere-grid-layer to the atmosphere
[709]528       CALL MPI_SEND( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, target_id, &
529                      tag, comm_inter, ierr )
[102]530
531    ENDIF
532
[667]533    CALL MPI_BARRIER( comm2d, ierr )
[102]534
[880]535#endif
536
[667]537  END SUBROUTINE interpolate_to_atmos
[102]538
[667]539
[1682]540!------------------------------------------------------------------------------!
541! Description:
542! ------------
543!> @todo Missing subroutine description.
544!------------------------------------------------------------------------------!
[709]545  SUBROUTINE interpolate_to_ocean( tag )
[667]546
[880]547#if defined( __parallel )
548
[1320]549    USE arrays_3d,                                                             &
550        ONLY:  total_2d_a, total_2d_o
[667]551
[1320]552    USE indices,                                                               &
553        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
554
555    USE kinds
556
[1324]557    USE pegrid
[1320]558
[667]559    IMPLICIT NONE
560
[1682]561    INTEGER(iwp)             ::  dnx !<
562    INTEGER(iwp)             ::  dny !<
563    INTEGER(iwp)             ::  i   !<
564    INTEGER(iwp)             ::  ii  !<
565    INTEGER(iwp)             ::  j   !<
566    INTEGER(iwp)             ::  jj  !<
567    INTEGER(iwp), intent(in) ::  tag !<
[667]568
[1682]569    REAL(wp)                 ::  fl  !<
570    REAL(wp)                 ::  fr  !<
571    REAL(wp)                 ::  myl !<
572    REAL(wp)                 ::  myr !<
[709]573
[667]574    CALL MPI_BARRIER( comm2d, ierr )
575
[709]576    IF ( myid == 0 )  THEN   
[667]577
578!
[709]579!--    Number of gridpoints of the fine grid within one mesh of the coarse grid
[667]580       dnx = ( nx_o + 1 ) / ( nx_a + 1 ) 
581       dny = ( ny_o + 1 ) / ( ny_a + 1 ) 
582
583!
[709]584!--    Cyclic boundary conditions for atmosphere grid
[667]585       total_2d_a(-nbgp:-1,:) = total_2d_a(ny+1-nbgp:ny,:)
586       total_2d_a(:,-nbgp:-1) = total_2d_a(:,nx+1-nbgp:nx)
587       
588       total_2d_a(ny+1:ny+nbgp,:) = total_2d_a(0:nbgp-1,:)
589       total_2d_a(:,nx+1:nx+nbgp) = total_2d_a(:,0:nbgp-1)
590!
[709]591!--    Bilinear Interpolation from atmosphere grid-layer to ocean grid-layer
[667]592       DO  j = 0, ny
593          DO  i = 0, nx
594             myl = ( total_2d_a(j+1,i)   - total_2d_a(j,i)   ) / dny
595             myr = ( total_2d_a(j+1,i+1) - total_2d_a(j,i+1) ) / dny
596             DO  jj = 0, dny-1
[709]597                fl = myl*jj + total_2d_a(j,i) 
598                fr = myr*jj + total_2d_a(j,i+1) 
[667]599                DO  ii = 0, dnx-1
600                   total_2d_o(j*dny+jj,i*dnx+ii) = ( fr - fl ) / dnx * ii + fl
601                ENDDO
602             ENDDO
603          ENDDO
604       ENDDO
605!
[709]606!--    Cyclic boundary conditions for ocean grid
[667]607       total_2d_o(-nbgp:-1,:) = total_2d_o(ny_o+1-nbgp:ny_o,:)
608       total_2d_o(:,-nbgp:-1) = total_2d_o(:,nx_o+1-nbgp:nx_o)
609
610       total_2d_o(ny_o+1:ny_o+nbgp,:) = total_2d_o(0:nbgp-1,:)
611       total_2d_o(:,nx_o+1:nx_o+nbgp) = total_2d_o(:,0:nbgp-1)
612
613       CALL MPI_SEND( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
614                      target_id, tag, comm_inter, ierr )
615
616    ENDIF
617
618    CALL MPI_BARRIER( comm2d, ierr ) 
619
[880]620#endif
621
[667]622  END SUBROUTINE interpolate_to_ocean
Note: See TracBrowser for help on using the repository browser.