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

Last change on this file since 709 was 709, checked in by raasch, 13 years ago

formatting adjustments

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