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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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