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

Last change on this file since 1419 was 1419, checked in by fricke, 10 years ago

last commit documented

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