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

Last change on this file since 1427 was 1427, checked in by maronga, 10 years ago

bugfix in surface coupler

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