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

Last change on this file since 1354 was 1354, checked in by heinze, 10 years ago

last commit documented

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