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

Last change on this file since 1319 was 1319, checked in by raasch, 10 years ago

last commit documented

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