source: palm/tags/release-3.9/SOURCE/surface_coupler.f90 @ 4012

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

last commit documented

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