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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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