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

Last change on this file since 1036 was 1036, checked in by raasch, 12 years ago

code has been put under the GNU General Public License (v3)

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