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

Last change on this file since 3045 was 3045, checked in by Giersch, 6 years ago

Code adjusted according to coding standards, renamed namelists, error messages revised until PA0347, output CASE 108 disabled

  • Property svn:keywords set to Id
File size: 31.8 KB
RevLine 
[1682]1!> @file surface_coupler.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]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!
[2718]17! Copyright 1997-2018 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[258]20! Current revisions:
[1092]21! ------------------
[1321]22!
[2233]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: surface_coupler.f90 3045 2018-05-28 07:55:41Z Giersch $
[3045]27! Error message revised
28!
29! 2718 2018-01-02 08:49:38Z maronga
[2716]30! Corrected "Former revisions" section
31!
32! 2696 2017-12-14 17:12:51Z kanani
33! Change in file header (GPL part)
[1321]34!
[2716]35! 2233 2017-05-30 18:08:54Z suehring
36!
[2233]37! 2232 2017-05-30 17:47:52Z suehring
38! Adjust to new surface structure. Transfer 1D surface fluxes onto 2D grid
39! (and back).
40!
[2032]41! 2031 2016-10-21 15:11:58Z knoop
42! renamed variable rho to rho_ocean
43!
[2001]44! 2000 2016-08-20 18:09:15Z knoop
45! Forced header and separation lines into 80 columns
46!
[1683]47! 1682 2015-10-07 23:56:08Z knoop
48! Code annotations made doxygen readable
49!
[1428]50! 1427 2014-07-07 14:04:59Z maronga
51! Bugfix: value of l_v corrected.
52!
[1419]53! 1418 2014-06-06 13:05:08Z fricke
54! Bugfix: For caluclation of the salinity flux at the sea surface,
55!          the given value for salinity must be in percent and not in psu
56!
[1354]57! 1353 2014-04-08 15:21:23Z heinze
58! REAL constants provided with KIND-attribute
59!
[1325]60! 1324 2014-03-21 09:13:16Z suehring
61! Bugfix: ONLY statement for module pegrid removed
62!
[1323]63! 1322 2014-03-20 16:38:49Z raasch
64! REAL constants defined as wp-kind
65!
[1321]66! 1320 2014-03-20 08:40:49Z raasch
[1320]67! ONLY-attribute added to USE-statements,
68! kind-parameters added to all INTEGER and REAL declaration statements,
69! kinds are defined in new module kinds,
70! old module precision_kind is removed,
71! revision history before 2012 removed,
72! comment fields (!:) to be used for variable explanations added to
73! all variable declaration statements
[102]74!
[1319]75! 1318 2014-03-17 13:35:16Z raasch
76! module interfaces removed
77!
[1093]78! 1092 2013-02-02 11:24:22Z raasch
79! unused variables removed
80!
[1037]81! 1036 2012-10-22 13:43:42Z raasch
82! code put under GPL (PALM 3.9)
83!
[881]84! 880 2012-04-13 06:28:59Z raasch
85! Bugfix: preprocessor statements for parallel execution added
86!
[110]87! 109 2007-08-28 15:26:47Z letzel
[102]88! Initial revision
89!
90! Description:
91! ------------
[1682]92!> Data exchange at the interface between coupled models
[102]93!------------------------------------------------------------------------------!
[1682]94 SUBROUTINE surface_coupler
95 
[102]96
[1320]97    USE arrays_3d,                                                             &
[2232]98        ONLY:  pt, rho_ocean, sa, total_2d_a, total_2d_o, u, v
[1320]99
[1427]100    USE cloud_parameters,                                                      &
101        ONLY:  cp, l_v
102
[1320]103    USE control_parameters,                                                    &
104        ONLY:  coupling_mode, coupling_mode_remote, coupling_topology,         &
[2232]105               humidity, humidity_remote, land_surface, message_string,        &
106               terminate_coupled, terminate_coupled_remote,                    &
107               time_since_reference_point, urban_surface
[1320]108
109    USE cpulog,                                                                &
110        ONLY:  cpu_log, log_point
111
112    USE indices,                                                               &
113        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_a, nx_o, ny, nyn, nyng, nys, &
114               nysg, ny_a, ny_o, nzt
115
116    USE kinds
117
[102]118    USE pegrid
119
[2232]120    USE surface_mod,                                                           &
121        ONLY :  surf_def_h, surf_lsm_h, surf_type, surf_usm_h
122
[102]123    IMPLICIT NONE
124
[2232]125    INTEGER(iwp) ::  i                                    !< index variable x-direction
126    INTEGER(iwp) ::  j                                    !< index variable y-direction
127    INTEGER(iwp) ::  m                                    !< running index for surface elements
128
129    REAL(wp)    ::  cpw = 4218.0_wp                       !< heat capacity of water at constant pressure
[1682]130    REAL(wp)    ::  time_since_reference_point_rem        !<
131    REAL(wp)    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp) !<
[102]132
[2232]133    REAL(wp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  surface_flux !< dummy array for surface fluxes on 2D grid
[1427]134
[2232]135
[206]136#if defined( __parallel )
[102]137
[667]138    CALL cpu_log( log_point(39), 'surface_coupler', 'start' )
[102]139
[667]140
141
[102]142!
[108]143!-- In case of model termination initiated by the remote model
144!-- (terminate_coupled_remote > 0), initiate termination of the local model.
145!-- The rest of the coupler must then be skipped because it would cause an MPI
146!-- intercomminucation hang.
147!-- If necessary, the coupler will be called at the beginning of the next
148!-- restart run.
[667]149
150    IF ( coupling_topology == 0 ) THEN
[709]151       CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER, target_id, &
152                          0,                                                   &
153                          terminate_coupled_remote, 1, MPI_INTEGER, target_id, &
[667]154                          0, comm_inter, status, ierr )
155    ELSE
156       IF ( myid == 0) THEN
157          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER, &
158                             target_id, 0,                             &
159                             terminate_coupled_remote, 1, MPI_INTEGER, & 
160                             target_id, 0,                             &
161                             comm_inter, status, ierr )
162       ENDIF
[709]163       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, &
164                       ierr )
[667]165
166       ALLOCATE( total_2d_a(-nbgp:ny_a+nbgp,-nbgp:nx_a+nbgp),       &
167                 total_2d_o(-nbgp:ny_o+nbgp,-nbgp:nx_o+nbgp) )
168
169    ENDIF
170
[108]171    IF ( terminate_coupled_remote > 0 )  THEN
[3045]172       WRITE( message_string, * ) 'remote model "',                            &
173                                  TRIM( coupling_mode_remote ),                &
174                                  '" terminated',                              &
175                                  ' with terminate_coupled_remote = ',         &
176                                  terminate_coupled_remote,                    &
177                                  ' local model  "', TRIM( coupling_mode ),    &
178                                  '" has',                                     &
179                                  ' terminate_coupled = ',                     &
[667]180                                   terminate_coupled
[258]181       CALL message( 'surface_coupler', 'PA0310', 1, 2, 0, 6, 0 )
[108]182       RETURN
183    ENDIF
[667]184 
[291]185
[108]186!
187!-- Exchange the current simulated time between the models,
[2232]188!-- currently just for total_2d
[709]189    IF ( coupling_topology == 0 ) THEN
190   
191       CALL MPI_SEND( time_since_reference_point, 1, MPI_REAL, target_id, 11, &
192                      comm_inter, ierr )
193       CALL MPI_RECV( time_since_reference_point_rem, 1, MPI_REAL, target_id, &
194                      11, comm_inter, status, ierr )
[667]195    ELSE
[709]196
[667]197       IF ( myid == 0 ) THEN
[709]198
199          CALL MPI_SEND( time_since_reference_point, 1, MPI_REAL, target_id, &
200                         11, comm_inter, ierr )
201          CALL MPI_RECV( time_since_reference_point_rem, 1, MPI_REAL,        &
[667]202                         target_id, 11, comm_inter, status, ierr )
[709]203
[667]204       ENDIF
[709]205
206       CALL MPI_BCAST( time_since_reference_point_rem, 1, MPI_REAL, 0, comm2d, &
207                       ierr )
208
[667]209    ENDIF
[102]210
211!
212!-- Exchange the interface data
213    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
[667]214   
215!
[709]216!--    Horizontal grid size and number of processors is equal in ocean and
217!--    atmosphere
218       IF ( coupling_topology == 0 )  THEN
[102]219
220!
[2232]221!--       Send heat flux at bottom surface to the ocean. First, transfer from
222!--       1D surface type to 2D grid.
223          CALL transfer_1D_to_2D_equal( surf_def_h(0)%shf, surf_lsm_h%shf,     &
224                                        surf_usm_h%shf )
225          CALL MPI_SEND( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, &
226                         12, comm_inter, ierr )
[102]227!
[2232]228!--       Send humidity flux at bottom surface to the ocean. First, transfer
229!--       from 1D surface type to 2D grid.
230          CALL transfer_1D_to_2D_equal( surf_def_h(0)%qsws, surf_lsm_h%qsws,   &
231                                        surf_usm_h%qsws )
[667]232          IF ( humidity )  THEN
[2232]233             CALL MPI_SEND( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL,         &
234                            target_id, 13, comm_inter, ierr )
[667]235          ENDIF
236!
[709]237!--       Receive temperature at the bottom surface from the ocean
[2232]238          CALL MPI_RECV( pt(0,nysg,nxlg), 1, type_xy, target_id, 14,           &
[709]239                         comm_inter, status, ierr )
[108]240!
[2232]241!--       Send the momentum flux (u) at bottom surface to the ocean. First,
242!--       transfer from 1D surface type to 2D grid.
243          CALL transfer_1D_to_2D_equal( surf_def_h(0)%usws, surf_lsm_h%usws,   &
244                                        surf_usm_h%usws )
245          CALL MPI_SEND( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, &
246                         15, comm_inter, ierr )
[102]247!
[2232]248!--       Send the momentum flux (v) at bottom surface to the ocean. First,
249!--       transfer from 1D surface type to 2D grid.
250          CALL transfer_1D_to_2D_equal( surf_def_h(0)%vsws, surf_lsm_h%vsws,   &
251                                        surf_usm_h%vsws )
252          CALL MPI_SEND( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, &
253                         16, comm_inter, ierr )
[102]254!
[709]255!--       Receive u at the bottom surface from the ocean
[2232]256          CALL MPI_RECV( u(0,nysg,nxlg), 1, type_xy, target_id, 17,            &
[709]257                         comm_inter, status, ierr )
[667]258!
[709]259!--       Receive v at the bottom surface from the ocean
[2232]260          CALL MPI_RECV( v(0,nysg,nxlg), 1, type_xy, target_id, 18,            &
[709]261                         comm_inter, status, ierr )
[667]262!
263!--    Horizontal grid size or number of processors differs between
264!--    ocean and atmosphere
265       ELSE
266     
267!
[709]268!--       Send heat flux at bottom surface to the ocean
[1353]269          total_2d_a = 0.0_wp
270          total_2d   = 0.0_wp
[2232]271!
272!--       Transfer from 1D surface type to 2D grid.
273          CALL transfer_1D_to_2D_unequal( surf_def_h(0)%shf, surf_lsm_h%shf,   &
274                                          surf_usm_h%shf )
[709]275
[2232]276          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0,  &
[709]277                           comm2d, ierr )
278          CALL interpolate_to_ocean( 12 )   
[667]279!
[709]280!--       Send humidity flux at bottom surface to the ocean
281          IF ( humidity )  THEN
[1353]282             total_2d_a = 0.0_wp
283             total_2d   = 0.0_wp
[2232]284!
285!--          Transfer from 1D surface type to 2D grid.
286             CALL transfer_1D_to_2D_unequal( surf_def_h(0)%qsws,              &
287                                             surf_lsm_h%qsws,                 &
288                                             surf_usm_h%qsws )
[709]289
290             CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, &
291                              0, comm2d, ierr )
292             CALL interpolate_to_ocean( 13 )
[667]293          ENDIF
294!
[709]295!--       Receive temperature at the bottom surface from the ocean
296          IF ( myid == 0 )  THEN
[2232]297             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL,          &
[667]298                            target_id, 14, comm_inter, status, ierr )   
299          ENDIF
300          CALL MPI_BARRIER( comm2d, ierr )
[709]301          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
302                          ierr )
[667]303          pt(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
304!
[709]305!--       Send momentum flux (u) at bottom surface to the ocean
[1353]306          total_2d_a = 0.0_wp 
307          total_2d   = 0.0_wp
[2232]308!
309!--       Transfer from 1D surface type to 2D grid.
310          CALL transfer_1D_to_2D_unequal( surf_def_h(0)%usws, surf_lsm_h%usws, &
311                                          surf_usm_h%usws )
[709]312          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0, &
313                           comm2d, ierr )
314          CALL interpolate_to_ocean( 15 )
[667]315!
[709]316!--       Send momentum flux (v) at bottom surface to the ocean
[1353]317          total_2d_a = 0.0_wp
318          total_2d   = 0.0_wp
[2232]319!
320!--       Transfer from 1D surface type to 2D grid.
321          CALL transfer_1D_to_2D_unequal( surf_def_h(0)%usws, surf_lsm_h%usws, &
322                                          surf_usm_h%usws )
[709]323          CALL MPI_REDUCE( total_2d, total_2d_a, ngp_a, MPI_REAL, MPI_SUM, 0, &
324                           comm2d, ierr )
325          CALL interpolate_to_ocean( 16 )
[667]326!
[709]327!--       Receive u at the bottom surface from the ocean
328          IF ( myid == 0 )  THEN
[667]329             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, &
[709]330                            target_id, 17, comm_inter, status, ierr )
[667]331          ENDIF
332          CALL MPI_BARRIER( comm2d, ierr )
[709]333          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
334                          ierr )
[667]335          u(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
336!
[709]337!--       Receive v at the bottom surface from the ocean
338          IF ( myid == 0 )  THEN
[667]339             CALL MPI_RECV( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, &
[709]340                            target_id, 18, comm_inter, status, ierr )
[667]341          ENDIF
342          CALL MPI_BARRIER( comm2d, ierr )
[709]343          CALL MPI_BCAST( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, 0, comm2d, &
344                          ierr )
[667]345          v(0,nysg:nyng,nxlg:nxrg) = total_2d_a(nysg:nyng,nxlg:nxrg)
346
347       ENDIF
348
[102]349    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
350
351!
[667]352!--    Horizontal grid size and number of processors is equal
353!--    in ocean and atmosphere
354       IF ( coupling_topology == 0 ) THEN
355!
[709]356!--       Receive heat flux at the sea surface (top) from the atmosphere
[2232]357          CALL MPI_RECV( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 12, &
[709]358                         comm_inter, status, ierr )
[2232]359          CALL transfer_2D_to_1D_equal( surf_def_h(2)%shf )
[102]360!
[709]361!--       Receive humidity flux from the atmosphere (bottom)
[667]362!--       and add it to the heat flux at the sea surface (top)...
363          IF ( humidity_remote )  THEN
[2232]364             CALL MPI_RECV( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, &
[667]365                            target_id, 13, comm_inter, status, ierr )
[2232]366             CALL transfer_2D_to_1D_equal( surf_def_h(2)%qsws )
[667]367          ENDIF
368!
369!--       Send sea surface temperature to the atmosphere model
[709]370          CALL MPI_SEND( pt(nzt,nysg,nxlg), 1, type_xy, target_id, 14, &
371                         comm_inter, ierr )
[667]372!
373!--       Receive momentum flux (u) at the sea surface (top) from the atmosphere
[2232]374          CALL MPI_RECV( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 15, &
[709]375                         comm_inter, status, ierr )
[2232]376          CALL transfer_2D_to_1D_equal( surf_def_h(2)%usws )
[667]377!
378!--       Receive momentum flux (v) at the sea surface (top) from the atmosphere
[2232]379          CALL MPI_RECV( surface_flux(nysg,nxlg), ngp_xy, MPI_REAL, target_id, 16, &
[709]380                         comm_inter, status, ierr )
[2232]381          CALL transfer_2D_to_1D_equal( surf_def_h(2)%vsws )
[667]382!
[709]383!--       Send u to the atmosphere
384          CALL MPI_SEND( u(nzt,nysg,nxlg), 1, type_xy, target_id, 17, &
385                         comm_inter, ierr )
[667]386!
[709]387!--       Send v to the atmosphere
388          CALL MPI_SEND( v(nzt,nysg,nxlg), 1, type_xy, target_id, 18, &
389                         comm_inter, ierr )
390!
[667]391!--    Horizontal gridsize or number of processors differs between
392!--    ocean and atmosphere
393       ELSE
394!
[709]395!--       Receive heat flux at the sea surface (top) from the atmosphere
396          IF ( myid == 0 )  THEN
[667]397             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]398                            target_id, 12, comm_inter, status, ierr )
[667]399          ENDIF
400          CALL MPI_BARRIER( comm2d, ierr )
[709]401          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, comm2d, &
402                          ierr )
[2232]403          CALL transfer_2D_to_1D_unequal( surf_def_h(2)%shf )
[667]404!
[709]405!--       Receive humidity flux at the sea surface (top) from the atmosphere
406          IF ( humidity_remote )  THEN
407             IF ( myid == 0 )  THEN
[667]408                CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]409                               target_id, 13, comm_inter, status, ierr )
[667]410             ENDIF
411             CALL MPI_BARRIER( comm2d, ierr )
[709]412             CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, &
413                             comm2d, ierr)
[2232]414             CALL transfer_2D_to_1D_unequal( surf_def_h(2)%qsws )
[667]415          ENDIF
416!
417!--       Send surface temperature to atmosphere
[1353]418          total_2d_o = 0.0_wp
419          total_2d   = 0.0_wp
[667]420          total_2d(nys:nyn,nxl:nxr) = pt(nzt,nys:nyn,nxl:nxr)
421
[709]422          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
423                           comm2d, ierr) 
424          CALL interpolate_to_atmos( 14 )
[667]425!
[709]426!--       Receive momentum flux (u) at the sea surface (top) from the atmosphere
427          IF ( myid == 0 )  THEN
[667]428             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]429                            target_id, 15, comm_inter, status, ierr )
[667]430          ENDIF
431          CALL MPI_BARRIER( comm2d, ierr )
432          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]433                          0, comm2d, ierr )
[2232]434          CALL transfer_2D_to_1D_unequal( surf_def_h(2)%usws )
[667]435!
[709]436!--       Receive momentum flux (v) at the sea surface (top) from the atmosphere
437          IF ( myid == 0 )  THEN
[667]438             CALL MPI_RECV( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
[709]439                            target_id, 16, comm_inter, status, ierr )
[667]440          ENDIF
441          CALL MPI_BARRIER( comm2d, ierr )
[709]442          CALL MPI_BCAST( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, 0, comm2d, &
443                          ierr )
[2232]444          CALL transfer_2D_to_1D_unequal( surf_def_h(2)%vsws )
[667]445!
446!--       Send u to atmosphere
[1353]447          total_2d_o = 0.0_wp 
448          total_2d   = 0.0_wp
[667]449          total_2d(nys:nyn,nxl:nxr) = u(nzt,nys:nyn,nxl:nxr)
[709]450          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
451                           comm2d, ierr )
452          CALL interpolate_to_atmos( 17 )
[667]453!
454!--       Send v to atmosphere
[1353]455          total_2d_o = 0.0_wp
456          total_2d   = 0.0_wp
[667]457          total_2d(nys:nyn,nxl:nxr) = v(nzt,nys:nyn,nxl:nxr)
[709]458          CALL MPI_REDUCE( total_2d, total_2d_o, ngp_o, MPI_REAL, MPI_SUM, 0, &
459                           comm2d, ierr )
460          CALL interpolate_to_atmos( 18 )
[667]461       
462       ENDIF
463
464!
465!--    Conversions of fluxes received from atmosphere
466       IF ( humidity_remote )  THEN
[108]467!
[2232]468!--       Here top heat flux is still the sum of atmospheric bottom heat fluxes,
[709]469!--       * latent heat of vaporization in m2/s2, or 540 cal/g, or 40.65 kJ/mol
470!--       /(rho_atm(=1.0)*c_p)
[2232]471          DO  m = 1, surf_def_h(2)%ns
472             i = surf_def_h(2)%i(m)
473             j = surf_def_h(2)%j(m)
474             
475             surf_def_h(2)%shf(m) = surf_def_h(2)%shf(m) +                     &
476                                    surf_def_h(2)%qsws(m) * l_v / cp
[709]477!
[2232]478!--          ...and convert it to a salinity flux at the sea surface (top)
479!--          following Steinhorn (1991), JPO 21, pp. 1681-1683:
480!--          S'w' = -S * evaporation / ( rho_water * ( 1 - S ) )
481             surf_def_h(2)%sasws(m) = -1.0_wp * sa(nzt,j,i) * 0.001_wp *       &
482                                      surf_def_h(2)%qsws(m) /                  &
483                                    ( rho_ocean(nzt,j,i) *                     &
484                                      ( 1.0_wp - sa(nzt,j,i) * 0.001_wp )      &
485                                    )
486          ENDDO
[108]487       ENDIF
488
489!
[102]490!--    Adjust the kinematic heat flux with respect to ocean density
[2232]491!--    (constants are the specific heat capacities for air and water), as well
492!--    as momentum fluxes
493       DO  m = 1, surf_def_h(2)%ns
494          i = surf_def_h(2)%i(m)
495          j = surf_def_h(2)%j(m)
496          surf_def_h(2)%shf(m) = surf_def_h(2)%shf(m) / rho_ocean(nzt,j,i) *   &
497                                 cp / cpw
[102]498
[2232]499          surf_def_h(2)%usws(m) = surf_def_h(2)%usws(m) / rho_ocean(nzt,j,i)
500          surf_def_h(2)%vsws(m) = surf_def_h(2)%vsws(m) / rho_ocean(nzt,j,i)
501       ENDDO
[102]502
[667]503    ENDIF
504
[709]505    IF ( coupling_topology == 1 )  THEN
[667]506       DEALLOCATE( total_2d_o, total_2d_a )
507    ENDIF
508
509    CALL cpu_log( log_point(39), 'surface_coupler', 'stop' )
510
511#endif
512
[2232]513     CONTAINS 
514
515!       Description:
516!------------------------------------------------------------------------------!
517!>      Data transfer from 1D surface-data type to 2D dummy array for equal
518!>      grids in atmosphere and ocean.
519!------------------------------------------------------------------------------!
520        SUBROUTINE transfer_1D_to_2D_equal( def_1d, lsm_1d, usm_1d )
521
522           IMPLICIT NONE
523
524            INTEGER(iwp) ::  i   !< running index x
525            INTEGER(iwp) ::  j   !< running index y
526            INTEGER(iwp) ::  m   !< running index surface type
527
528            REAL(wp), DIMENSION(1:surf_def_h(0)%ns) ::  def_1d !< 1D surface flux, default surfaces
529            REAL(wp), DIMENSION(1:surf_lsm_h%ns)    ::  lsm_1d !< 1D surface flux, natural surfaces
530            REAL(wp), DIMENSION(1:surf_usm_h%ns)    ::  usm_1d !< 1D surface flux, urban surfaces
531!
532!--         Transfer surface flux at default surfaces to 2D grid
533            DO  m = 1, surf_def_h(0)%ns
534               i = surf_def_h(0)%i(m)
535               j = surf_def_h(0)%j(m)
536               surface_flux(j,i) = def_1d(m)
537            ENDDO
538!
539!--         Transfer surface flux at natural surfaces to 2D grid
540            IF ( land_surface )  THEN
541               DO  m = 1, SIZE(lsm_1d)
542                  i = surf_lsm_h%i(m)
543                  j = surf_lsm_h%j(m)
544                  surface_flux(j,i) = lsm_1d(m)
545               ENDDO
546            ENDIF
547!
548!--         Transfer surface flux at natural surfaces to 2D grid
549            IF ( urban_surface )  THEN
550               DO  m = 1, SIZE(usm_1d)
551                  i = surf_usm_h%i(m)
552                  j = surf_usm_h%j(m)
553                  surface_flux(j,i) = usm_1d(m)
554               ENDDO
555            ENDIF
556
557        END SUBROUTINE transfer_1D_to_2D_equal
558
559!       Description:
560!------------------------------------------------------------------------------!
561!>      Data transfer from 2D array for equal grids onto 1D surface-data type
562!>      array.
563!------------------------------------------------------------------------------!
564        SUBROUTINE transfer_2D_to_1D_equal( def_1d )
565
566           IMPLICIT NONE
567
568            INTEGER(iwp) ::  i   !< running index x
569            INTEGER(iwp) ::  j   !< running index y
570            INTEGER(iwp) ::  m   !< running index surface type
571
572            REAL(wp), DIMENSION(1:surf_def_h(2)%ns) ::  def_1d !< 1D surface flux, default surfaces
573!
574!--         Transfer surface flux to 1D surface type, only for default surfaces
575            DO  m = 1, surf_def_h(2)%ns
576               i = surf_def_h(2)%i(m)
577               j = surf_def_h(2)%j(m)
578               def_1d(m) = surface_flux(j,i)
579            ENDDO
580
581        END SUBROUTINE transfer_2D_to_1D_equal
582
583!       Description:
584!------------------------------------------------------------------------------!
585!>      Data transfer from 1D surface-data type to 2D dummy array from unequal
586!>      grids in atmosphere and ocean.
587!------------------------------------------------------------------------------!
588        SUBROUTINE transfer_1D_to_2D_unequal( def_1d, lsm_1d, usm_1d )
589
590           IMPLICIT NONE
591
592            INTEGER(iwp) ::  i   !< running index x
593            INTEGER(iwp) ::  j   !< running index y
594            INTEGER(iwp) ::  m   !< running index surface type
595
596            REAL(wp), DIMENSION(1:surf_def_h(0)%ns) ::  def_1d !< 1D surface flux, default surfaces
597            REAL(wp), DIMENSION(1:surf_lsm_h%ns)    ::  lsm_1d !< 1D surface flux, natural surfaces
598            REAL(wp), DIMENSION(1:surf_usm_h%ns)    ::  usm_1d !< 1D surface flux, urban surfaces
599!
600!--         Transfer surface flux at default surfaces to 2D grid. Transfer no
601!--         ghost-grid points since total_2d is a global array.
602            DO  m = 1, SIZE(def_1d)
603               i = surf_def_h(0)%i(m)
604               j = surf_def_h(0)%j(m)
605
606               IF ( i >= nxl  .AND.  i <= nxr  .AND.                           &
607                    j >= nys  .AND.  j <= nyn )  THEN
608                  total_2d(j,i) = def_1d(m)
609               ENDIF
610            ENDDO
611!
612!--         Transfer surface flux at natural surfaces to 2D grid
613            IF ( land_surface )  THEN
614               DO  m = 1, SIZE(lsm_1d)
615                  i = surf_lsm_h%i(m)
616                  j = surf_lsm_h%j(m)
617
618                  IF ( i >= nxl  .AND.  i <= nxr  .AND.                        &
619                       j >= nys  .AND.  j <= nyn )  THEN
620                     total_2d(j,i) = lsm_1d(m)
621                  ENDIF
622               ENDDO
623            ENDIF
624!
625!--         Transfer surface flux at natural surfaces to 2D grid
626            IF ( urban_surface )  THEN
627               DO  m = 1, SIZE(usm_1d)
628                  i = surf_usm_h%i(m)
629                  j = surf_usm_h%j(m)
630
631                  IF ( i >= nxl  .AND.  i <= nxr  .AND.                        &
632                       j >= nys  .AND.  j <= nyn )  THEN
633                     total_2d(j,i) = usm_1d(m)
634                  ENDIF
635               ENDDO
636            ENDIF
637
638        END SUBROUTINE transfer_1D_to_2D_unequal
639
640!       Description:
641!------------------------------------------------------------------------------!
642!>      Data transfer from 2D dummy array from unequal grids to 1D surface-data
643!>      type.
644!------------------------------------------------------------------------------!
645        SUBROUTINE transfer_2D_to_1D_unequal( def_1d )
646
647           IMPLICIT NONE
648
649            INTEGER(iwp) ::  i   !< running index x
650            INTEGER(iwp) ::  j   !< running index y
651            INTEGER(iwp) ::  m   !< running index surface type
652
653            REAL(wp), DIMENSION(1:surf_def_h(2)%ns) ::  def_1d !< 1D surface flux, default surfaces
654!
655!--         Transfer 2D surface flux to default surfaces data type. Transfer no
656!--         ghost-grid points since total_2d is a global array.
657            DO  m = 1, SIZE(def_1d)
658               i = surf_def_h(2)%i(m)
659               j = surf_def_h(2)%j(m)
660
661               IF ( i >= nxl  .AND.  i <= nxr  .AND.                           &
662                    j >= nys  .AND.  j <= nyn )  THEN
663                  def_1d(m) = total_2d_o(j,i)
664               ENDIF
665            ENDDO
666
667
668        END SUBROUTINE transfer_2D_to_1D_unequal
669
[667]670  END SUBROUTINE surface_coupler
671
672
673
[1682]674!------------------------------------------------------------------------------!
675! Description:
676! ------------
677!> @todo Missing subroutine description.
678!------------------------------------------------------------------------------!
[709]679  SUBROUTINE interpolate_to_atmos( tag )
[667]680
[880]681#if defined( __parallel )
682
[1320]683    USE arrays_3d,                                                             &
684        ONLY:  total_2d_a, total_2d_o
[667]685
[1320]686    USE indices,                                                               &
687        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
688
689    USE kinds
690
[1324]691    USE pegrid
[1320]692
[667]693    IMPLICIT NONE
694
[1682]695    INTEGER(iwp) ::  dnx  !<
696    INTEGER(iwp) ::  dnx2 !<
697    INTEGER(iwp) ::  dny  !<
698    INTEGER(iwp) ::  dny2 !<
699    INTEGER(iwp) ::  i    !<
700    INTEGER(iwp) ::  ii   !<
701    INTEGER(iwp) ::  j    !<
702    INTEGER(iwp) ::  jj   !<
[667]703
[1682]704    INTEGER(iwp), intent(in) ::  tag !<
[1320]705
[667]706    CALL MPI_BARRIER( comm2d, ierr )
707
[709]708    IF ( myid == 0 )  THEN
709!
710!--    Cyclic boundary conditions for the total 2D-grid
[667]711       total_2d_o(-nbgp:-1,:) = total_2d_o(ny+1-nbgp:ny,:)
712       total_2d_o(:,-nbgp:-1) = total_2d_o(:,nx+1-nbgp:nx)
713
714       total_2d_o(ny+1:ny+nbgp,:) = total_2d_o(0:nbgp-1,:)
715       total_2d_o(:,nx+1:nx+nbgp) = total_2d_o(:,0:nbgp-1)
716
[102]717!
[667]718!--    Number of gridpoints of the fine grid within one mesh of the coarse grid
719       dnx = (nx_o+1) / (nx_a+1) 
720       dny = (ny_o+1) / (ny_a+1) 
[102]721
722!
[709]723!--    Distance for interpolation around coarse grid points within the fine
724!--    grid (note: 2*dnx2 must not be equal with dnx)
[667]725       dnx2 = 2 * ( dnx / 2 )
726       dny2 = 2 * ( dny / 2 )
[102]727
[1353]728       total_2d_a = 0.0_wp
[102]729!
[667]730!--    Interpolation from ocean-grid-layer to atmosphere-grid-layer
731       DO  j = 0, ny_a
732          DO  i = 0, nx_a 
733             DO  jj = 0, dny2
734                DO  ii = 0, dnx2
735                   total_2d_a(j,i) = total_2d_a(j,i) &
736                                     + total_2d_o(j*dny+jj,i*dnx+ii)
737                ENDDO
738             ENDDO
739             total_2d_a(j,i) = total_2d_a(j,i) / ( ( dnx2 + 1 ) * ( dny2 + 1 ) )
740          ENDDO
741       ENDDO
742!
[709]743!--    Cyclic boundary conditions for atmosphere grid
[667]744       total_2d_a(-nbgp:-1,:) = total_2d_a(ny_a+1-nbgp:ny_a,:)
745       total_2d_a(:,-nbgp:-1) = total_2d_a(:,nx_a+1-nbgp:nx_a)
746       
747       total_2d_a(ny_a+1:ny_a+nbgp,:) = total_2d_a(0:nbgp-1,:)
748       total_2d_a(:,nx_a+1:nx_a+nbgp) = total_2d_a(:,0:nbgp-1)
749!
750!--    Transfer of the atmosphere-grid-layer to the atmosphere
[709]751       CALL MPI_SEND( total_2d_a(-nbgp,-nbgp), ngp_a, MPI_REAL, target_id, &
752                      tag, comm_inter, ierr )
[102]753
754    ENDIF
755
[667]756    CALL MPI_BARRIER( comm2d, ierr )
[102]757
[880]758#endif
759
[667]760  END SUBROUTINE interpolate_to_atmos
[102]761
[667]762
[1682]763!------------------------------------------------------------------------------!
764! Description:
765! ------------
766!> @todo Missing subroutine description.
767!------------------------------------------------------------------------------!
[709]768  SUBROUTINE interpolate_to_ocean( tag )
[667]769
[880]770#if defined( __parallel )
771
[1320]772    USE arrays_3d,                                                             &
773        ONLY:  total_2d_a, total_2d_o
[667]774
[1320]775    USE indices,                                                               &
776        ONLY:  nbgp, nx, nx_a, nx_o, ny, ny_a, ny_o
777
778    USE kinds
779
[1324]780    USE pegrid
[1320]781
[667]782    IMPLICIT NONE
783
[1682]784    INTEGER(iwp)             ::  dnx !<
785    INTEGER(iwp)             ::  dny !<
786    INTEGER(iwp)             ::  i   !<
787    INTEGER(iwp)             ::  ii  !<
788    INTEGER(iwp)             ::  j   !<
789    INTEGER(iwp)             ::  jj  !<
790    INTEGER(iwp), intent(in) ::  tag !<
[667]791
[1682]792    REAL(wp)                 ::  fl  !<
793    REAL(wp)                 ::  fr  !<
794    REAL(wp)                 ::  myl !<
795    REAL(wp)                 ::  myr !<
[709]796
[667]797    CALL MPI_BARRIER( comm2d, ierr )
798
[709]799    IF ( myid == 0 )  THEN   
[667]800
801!
[709]802!--    Number of gridpoints of the fine grid within one mesh of the coarse grid
[667]803       dnx = ( nx_o + 1 ) / ( nx_a + 1 ) 
804       dny = ( ny_o + 1 ) / ( ny_a + 1 ) 
805
806!
[709]807!--    Cyclic boundary conditions for atmosphere grid
[667]808       total_2d_a(-nbgp:-1,:) = total_2d_a(ny+1-nbgp:ny,:)
809       total_2d_a(:,-nbgp:-1) = total_2d_a(:,nx+1-nbgp:nx)
810       
811       total_2d_a(ny+1:ny+nbgp,:) = total_2d_a(0:nbgp-1,:)
812       total_2d_a(:,nx+1:nx+nbgp) = total_2d_a(:,0:nbgp-1)
813!
[709]814!--    Bilinear Interpolation from atmosphere grid-layer to ocean grid-layer
[667]815       DO  j = 0, ny
816          DO  i = 0, nx
817             myl = ( total_2d_a(j+1,i)   - total_2d_a(j,i)   ) / dny
818             myr = ( total_2d_a(j+1,i+1) - total_2d_a(j,i+1) ) / dny
819             DO  jj = 0, dny-1
[709]820                fl = myl*jj + total_2d_a(j,i) 
821                fr = myr*jj + total_2d_a(j,i+1) 
[667]822                DO  ii = 0, dnx-1
823                   total_2d_o(j*dny+jj,i*dnx+ii) = ( fr - fl ) / dnx * ii + fl
824                ENDDO
825             ENDDO
826          ENDDO
827       ENDDO
828!
[709]829!--    Cyclic boundary conditions for ocean grid
[667]830       total_2d_o(-nbgp:-1,:) = total_2d_o(ny_o+1-nbgp:ny_o,:)
831       total_2d_o(:,-nbgp:-1) = total_2d_o(:,nx_o+1-nbgp:nx_o)
832
833       total_2d_o(ny_o+1:ny_o+nbgp,:) = total_2d_o(0:nbgp-1,:)
834       total_2d_o(:,nx_o+1:nx_o+nbgp) = total_2d_o(:,0:nbgp-1)
835
836       CALL MPI_SEND( total_2d_o(-nbgp,-nbgp), ngp_o, MPI_REAL, &
837                      target_id, tag, comm_inter, ierr )
838
839    ENDIF
840
841    CALL MPI_BARRIER( comm2d, ierr ) 
842
[880]843#endif
844
[667]845  END SUBROUTINE interpolate_to_ocean
Note: See TracBrowser for help on using the repository browser.