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

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

unused variables remove from several routines

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