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

Last change on this file since 1325 was 1325, checked in by suehring, 10 years ago

last commit documented

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