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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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