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

Last change on this file since 1952 was 1818, checked in by maronga, 8 years ago

last commit documented / copyright update

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