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

Last change on this file since 1093 was 1093, checked in by raasch, 11 years ago

last commit documented

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