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

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

Bugfixes in ONLY statements

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