Changeset 75 for palm/trunk/SOURCE


Ignore:
Timestamp:
Mar 22, 2007 9:54:05 AM (17 years ago)
Author:
raasch
Message:

preliminary update for changes concerning non-cyclic boundary conditions

Location:
palm/trunk/SOURCE
Files:
41 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/CURRENT_MODIFICATIONS

    r73 r75  
    3333Changed:
    3434-------
    35 General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d
     35General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, volume flow control is added for the outflow boundary (currently only for the north boundary!!), additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d
    3636
    3737+age_m in particle_type
     
    4848q is not allowed to become negative (prognostic_equations).
    4949
     50poisfft_init is only called if fft-solver is switched on (init_pegrid).
     51
     52d3par-parameter moisture renamed to humidity.
     53
     54Subversion global revision number is read from mrun and added to the run description header and to the run control (_rc) file.
     55
    5056__vtk directives removed from main program.
    5157
    5258The uitility routine interpret_config reads PALM environment variables from NAMELIST instead using the system call GETENV.
    5359
    54 check_parameters, data_output_dvrp, data_output_ptseries, data_output_ts, exchange_horiz_2d, flow_statistics, header, init_particles, init_pegrid, init_3d_model, modules, palm, package_parin, parin, prognostic_equations, read_3d_binary, time_integration, write_3d_binary
     60advec_u_pw, advec_u_up, advec_v_pw, advec_v_up, asselin_filter, check_parameters, coriolis, data_output_dvrp, data_output_ptseries, data_output_ts, data_output_2d, data_output_3d, diffusion_u, diffusion_v, exchange_horiz, exchange_horiz_2d, flow_statistics, header, init_grid, init_particles, init_pegrid, init_rankine, init_pt_anomaly, init_1d_model, init_3d_model, modules, palm, package_parin, parin, poismg, prandtl_fluxes, pres, production_e, prognostic_equations, read_var_list, read_3d_binary, sor, swap_timelevel, time_integration, write_var_list, write_3d_binary
    5561
    5662
  • palm/trunk/SOURCE/advec_particles.f90

    r64 r75  
    99! + user_advec_particles, particles-package is now part of the defaut code,
    1010! array arguments in sendrecv calls have to refer to first element (1) due to
    11 ! mpich (mpiI) interface requirements
     11! mpich (mpiI) interface requirements,
     12! 2nd+3rd argument removed from exchange horiz
    1213! TEST: PRINT statements on unit 9 (commented out)
    1314!
     
    662663!
    663664!--    Lateral boundary conditions
    664        CALL exchange_horiz( de_dx, 0, 0 )
    665        CALL exchange_horiz( de_dy, 0, 0 )
    666        CALL exchange_horiz( de_dz, 0, 0 )
    667        CALL exchange_horiz( diss,  0, 0 )
     665       CALL exchange_horiz( de_dx )
     666       CALL exchange_horiz( de_dy )
     667       CALL exchange_horiz( de_dz )
     668       CALL exchange_horiz( diss  )
    668669
    669670!
  • palm/trunk/SOURCE/advec_u_pw.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! uxrp eliminated
    77!
    88! Former revisions:
     
    5454       gu = 2.0 * u_gtrans
    5555       gv = 2.0 * v_gtrans
    56        DO  i = nxl, nxr+uxrp
     56       DO  i = nxl, nxr
    5757          DO  j = nys, nyn
    5858             DO  k = nzb_u_inner(j,i)+1, nzt
  • palm/trunk/SOURCE/advec_u_up.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! uxrp eliminated
    77!
    88! Former revisions:
     
    5353
    5454
    55        DO  i = nxl, nxr+uxrp
     55       DO  i = nxl, nxr
    5656          DO  j = nys, nyn
    5757             DO  k = nzb_u_inner(j,i)+1, nzt
  • palm/trunk/SOURCE/advec_v_pw.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! vynp eliminated
    77!
    88! Former revisions:
     
    5656       gv = 2.0 * v_gtrans
    5757       DO  i = nxl, nxr
    58           DO  j = nys, nyn+vynp
     58          DO  j = nys, nyn
    5959             DO  k = nzb_v_inner(j,i)+1, nzt
    6060                tend(k,j,i) = tend(k,j,i) - 0.25 * (                           &
  • palm/trunk/SOURCE/advec_v_up.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! vynp eliminated
    77!
    88! Former revisions:
     
    5353
    5454       DO  i = nxl, nxr
    55           DO  j = nys, nyn+vynp
     55          DO  j = nys, nyn
    5656             DO  k = nzb_v_inner(j,i)+1, nzt
    5757!
  • palm/trunk/SOURCE/asselin_filter.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! moisture renamed humidity
    77!
    88! Former revisions:
     
    7272          ENDIF
    7373
    74           IF ( ( moisture .OR. passive_scalar )  .AND. &
     74          IF ( ( humidity .OR. passive_scalar )  .AND. &
    7575             scalar_advec /= 'bc-scheme' )  THEN
    7676             DO  k = nzb_2d(j,i), nzt+1
     
    9696    ENDIF
    9797
    98     IF ( ( moisture .OR. passive_scalar )  .AND. &
     98    IF ( ( humidity .OR. passive_scalar )  .AND. &
    9999         scalar_advec /= 'bc-scheme' )  THEN
    100100       q = q + asselin_filter_factor * ( q_p - 2.0 * q + q_m )
  • palm/trunk/SOURCE/boundary_conds.f90

    r73 r75  
    44! Actual revisions:
    55! -----------------
    6 ! The "main" part sets conditions for time level t+dt insteat of level t,
    7 ! outflow boundary conditions changed from Neumann to radiation condition
     6! The "main" part sets conditions for time level t+dt instead of level t,
     7! outflow boundary conditions changed from Neumann to radiation condition,
     8! uxrp, vynp eliminated, moisture renamed humidity
    89!
    910! Former revisions:
     
    126127!--    Boundary conditions for total water content or scalar,
    127128!--    bottom and surface boundary (see also temperature)
    128        IF ( moisture  .OR.  passive_scalar )  THEN
    129 !
    130 !--       Surface conditions for constant_moisture_flux
     129       IF ( humidity  .OR.  passive_scalar )  THEN
     130!
     131!--       Surface conditions for constant_humidity_flux
    131132          IF ( ibc_q_b == 0 ) THEN
    132133             DO  i = nxl-1, nxr+1
     
    154155          v_p(:,nys,:) = v_p(:,nys-1,:)
    155156       ELSEIF ( inflow_n ) THEN
    156           v_p(:,nyn+vynp,:) = v_p(:,nyn+vynp+1,:)
     157          v_p(:,nyn,:) = v_p(:,nyn+1,:)
    157158       ELSEIF ( inflow_l ) THEN
    158159          u_p(:,:,nxl) = u_p(:,:,nxl-1)
    159160       ELSEIF ( inflow_r ) THEN
    160           u_p(:,:,nxr+uxrp) = u_p(:,:,nxr+uxrp+1)
     161          u_p(:,:,nxr) = u_p(:,:,nxr+1)
    161162       ENDIF
    162163
     
    166167          pt_p(:,nys-1,:)     = pt_p(:,nys,:)
    167168          IF ( .NOT. constant_diffusion     )  e_p(:,nys-1,:) = e_p(:,nys,:)
    168           IF ( moisture .OR. passive_scalar )  q_p(:,nys-1,:) = q_p(:,nys,:)
     169          IF ( humidity .OR. passive_scalar )  q_p(:,nys-1,:) = q_p(:,nys,:)
    169170       ELSEIF ( outflow_n )  THEN
    170171          pt_p(:,nyn+1,:)     = pt_p(:,nyn,:)
    171172          IF ( .NOT. constant_diffusion     )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
    172           IF ( moisture .OR. passive_scalar )  q_p(:,nyn+1,:) = q_p(:,nyn,:)
     173          IF ( humidity .OR. passive_scalar )  q_p(:,nyn+1,:) = q_p(:,nyn,:)
    173174       ELSEIF ( outflow_l )  THEN
    174175          pt_p(:,:,nxl-1)     = pt_p(:,:,nxl)
    175176          IF ( .NOT. constant_diffusion     )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
    176           IF ( moisture .OR. passive_scalar )  q_p(:,:,nxl-1) = q_p(:,:,nxl)     
     177          IF ( humidity .OR. passive_scalar )  q_p(:,:,nxl-1) = q_p(:,:,nxl)
    177178       ELSEIF ( outflow_r )  THEN
    178179          pt_p(:,:,nxr+1)     = pt_p(:,:,nxr)
    179180          IF ( .NOT. constant_diffusion     )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
    180           IF ( moisture .OR. passive_scalar )  q_p(:,:,nxr+1) = q_p(:,:,nxr)
     181          IF ( humidity .OR. passive_scalar )  q_p(:,:,nxr+1) = q_p(:,:,nxr)
    181182       ENDIF
    182183
    183184    ENDIF
    184185
    185     IF ( range == 'outflow_uvw' ) THEN
    186 !
    187 !--    Radiation boundary condition for the velocities at the respective outflow
    188        IF ( outflow_s ) THEN
    189 !          v(:,nys-1,:) = v(:,nys,:)
    190 !          w(:,nys-1,:) = 0.0
    191 !!
    192 !!--       Compute the mean horizontal wind parallel to and within the outflow
    193 !!--       wall and use this as boundary condition for u
    194 !#if defined( __parallel )
    195 !          CALL MPI_ALLREDUCE( uvmean_outflow_l, uvmean_outflow, nzt-nzb+2, &
    196 !                              MPI_REAL, MPI_SUM, comm1dx, ierr )
    197 !          uvmean_outflow = uvmean_outflow / ( nx + 1.0 )
    198 !#else
    199 !          uvmean_outflow = uvmean_outflow_l / ( nx + 1.0 )
    200 !#endif
    201 !          DO  k = nzb, nzt+1
    202 !             u(k,nys-1,:) = uvmean_outflow(k)
    203 !          ENDDO
    204        ENDIF
    205 
    206        IF ( outflow_n  .AND.                                                 &
    207             intermediate_timestep_count == intermediate_timestep_count_max ) &
    208        THEN
    209 
    210           c_max = dy / dt_3d
    211 
    212           DO i = nxl-1, nxr+1
    213              DO k = nzb+1, nzt+1
    214 
    215 !
    216 !--             First calculate the phase speeds for u,v, and w
    217                 denom = u_m_n(k,ny,i,-2) - u_m_n(k,ny-1,i,-2)
    218 
    219                 IF ( denom /= 0.0 )  THEN
    220                    c_u = -c_max * ( u_m_n(k,ny,i,-1)-u_m_n(k,ny,i,-2) ) / denom
    221                    IF ( c_u < 0.0 )  THEN
    222                       c_u = 0.0
    223                    ELSEIF ( c_u > c_max )  THEN
    224                       c_u = c_max
    225                    ENDIF
    226                 ELSE
     186!
     187!-- Radiation boundary condition for the velocities at the respective outflow
     188    IF ( outflow_s  .AND.                                                 &
     189         intermediate_timestep_count == intermediate_timestep_count_max ) &
     190    THEN
     191
     192       c_max = dy / dt_3d
     193
     194       DO i = nxl-1, nxr+1
     195          DO k = nzb+1, nzt+1
     196
     197!
     198!--          First calculate the phase speeds for u,v, and w
     199             denom = u_m_s(k,0,i) - u_m_s(k,1,i)
     200
     201             IF ( denom /= 0.0 )  THEN
     202                c_u = -c_max * ( u(k,0,i) - u_m_s(k,0,i) ) / denom
     203                IF ( c_u < 0.0 )  THEN
     204                   c_u = 0.0
     205                ELSEIF ( c_u > c_max )  THEN
    227206                   c_u = c_max
    228207                ENDIF
    229 
    230                 denom = v_m_n(k,ny,i,-2) - v_m_n(k,ny-1,i,-2)
    231 
    232                 IF ( denom /= 0.0 )  THEN
    233                    c_v = -c_max * ( v_m_n(k,ny,i,-1)-v_m_n(k,ny,i,-2) ) / denom
    234                    IF ( c_v < 0.0 )  THEN
    235                       c_v = 0.0
    236                    ELSEIF ( c_v > c_max )  THEN
    237                       c_v = c_max
    238                    ENDIF
    239                 ELSE
     208             ELSE
     209                c_u = c_max
     210             ENDIF
     211             denom = v_m_s(k,0,i) - v_m_s(k,1,i)
     212
     213             IF ( denom /= 0.0 )  THEN
     214                c_v = -c_max * ( v(k,0,i) - v_m_s(k,0,i) ) / denom
     215                IF ( c_v < 0.0 )  THEN
     216                   c_v = 0.0
     217                ELSEIF ( c_v > c_max )  THEN
    240218                   c_v = c_max
    241219                ENDIF
    242 
    243                 denom = w_m_n(k,ny,i,-2) - w_m_n(k,ny-1,i,-2)
    244 
    245                 IF ( denom /= 0.0 )  THEN
    246                    c_w = -c_max * ( w_m_n(k,ny,i,-1)-w_m_n(k,ny,i,-2) ) / denom
    247                    IF ( c_w < 0.0 )  THEN
    248                       c_w = 0.0
    249                    ELSEIF ( c_w > c_max )  THEN
    250                       c_w = c_max
    251                    ENDIF
    252                 ELSE
     220             ELSE
     221                c_v = c_max
     222             ENDIF
     223
     224             denom = w_m_s(k,0,i) - w_m_s(k,1,i)
     225
     226             IF ( denom /= 0.0 )  THEN
     227                c_w = -c_max * ( w(k,0,i) - w_m_s(k,0,i) ) / denom
     228                IF ( c_w < 0.0 )  THEN
     229                   c_w = 0.0
     230                ELSEIF ( c_w > c_max )  THEN
    253231                   c_w = c_max
    254232                ENDIF
    255 
    256 !
    257 !--             Calculate the new velocities
    258                 u(k,ny+1,i) = u_m_n(k,ny+1,i,-1) - dt_3d * c_u * &
    259                               ( u_m_n(k,ny+1,i,-1) - u_m_n(k,ny,i,-1) ) * ddy
    260 
    261                 v(k,ny+1,i) = v_m_n(k,ny+1,i,-1) - dt_3d * c_v * &
    262                               ( v_m_n(k,ny+1,i,-1) - v_m_n(k,ny,i,-1) ) * ddy
    263 
    264                 w(k,ny+1,i) = w_m_n(k,ny+1,i,-1) - dt_3d * c_w * &
    265                               ( w_m_n(k,ny+1,i,-1) - w_m_n(k,ny,i,-1) ) * ddy
    266 
    267 !
    268 !--             Swap timelevels for the next timestep
    269                 u_m_n(k,:,i,-2) = u_m_n(k,:,i,-1)
    270                 u_m_n(k,:,i,-1) = u(k,ny-1:ny+1,i)
    271                 v_m_n(k,:,i,-2) = v_m_n(k,:,i,-1)
    272                 v_m_n(k,:,i,-1) = v(k,ny-1:ny+1,i)
    273                 w_m_n(k,:,i,-2) = w_m_n(k,:,i,-1)
    274                 w_m_n(k,:,i,-1) = w(k,ny-1:ny+1,i)
    275 
    276              ENDDO
    277           ENDDO
    278 
    279 !
    280 !--       Bottom boundary at the outflow
    281           IF ( ibc_uv_b == 0 )  THEN
    282              u(nzb,ny+1,:) = -u(nzb+1,ny+1,:)
    283              v(nzb,ny+1,:) = -v(nzb+1,ny+1,:) 
    284           ELSE                   
    285              u(nzb,ny+1,:) =  u(nzb+1,ny+1,:)
    286              v(nzb,ny+1,:) =  v(nzb+1,ny+1,:)
    287           ENDIF
    288           w(nzb,ny+1,:) = 0.0
    289 
    290 !
    291 !--       Top boundary at the outflow
    292           IF ( ibc_uv_t == 0 )  THEN
    293              u(nzt+1,ny+1,:) = ug(nzt+1)
    294              v(nzt+1,ny+1,:) = vg(nzt+1)
    295           ELSE
    296              u(nzt+1,ny+1,:) = u(nzt,nyn+1,:)
    297              v(nzt+1,ny+1,:) = v(nzt,nyn+1,:)
    298           ENDIF
    299           w(nzt:nzt+1,ny+1,:) = 0.0
    300 
    301        ENDIF
    302 
    303        IF ( outflow_l ) THEN
    304 !          u(:,:,nxl-1) = u(:,:,nxl)
    305 !          w(:,:,nxl-1) = 0.0
    306 !
    307 !--       Compute the mean horizontal wind parallel to and within the outflow
    308 !--       wall and use this as boundary condition for v
    309 !#if defined( __parallel )
    310 !          CALL MPI_ALLREDUCE( uvmean_outflow_l, uvmean_outflow, nzt-nzb+2, &
    311 !                              MPI_REAL, MPI_SUM, comm1dy, ierr )
    312 !          uvmean_outflow = uvmean_outflow / ( ny + 1.0 )
    313 !#else
    314 !          uvmean_outflow = uvmean_outflow_l / ( ny + 1.0 )
    315 !#endif
    316 !          DO  k = nzb, nzt+1
    317 !             v(k,:,nxl-1) = uvmean_outflow(k)
    318 !          ENDDO   
    319 !
    320        ENDIF
    321 
    322        IF ( outflow_r  .AND.                                                 &
    323             intermediate_timestep_count == intermediate_timestep_count_max ) &
    324        THEN
    325 
    326           c_max = dx / dt_3d
    327 
    328           DO j = nys-1, nyn+1
    329              DO k = nzb+1, nzt+1
    330 
    331 !
    332 !--             First calculate the phase speeds for u,v, and w
    333                 denom = u_m_r(k,j,nx,-2) - u_m_r(k,j,nx-1,-2)
    334 
    335                 IF ( denom /= 0.0 )  THEN
    336                    c_u = -c_max * ( u_m_r(k,j,nx,-1)-u_m_r(k,j,nx,-2) ) / denom
    337                    IF ( c_u < 0.0 )  THEN
    338                       c_u = 0.0
    339                    ELSEIF ( c_u > c_max )  THEN
    340                       c_u = c_max
    341                    ENDIF
    342                 ELSE
     233             ELSE
     234                c_w = c_max
     235             ENDIF
     236
     237!
     238!--          Calculate the new velocities
     239             u_p(k,-1,i) = u(k,-1,i) + dt_3d * c_u * &
     240                                       ( u(k,-1,i) - u(k,0,i) ) * ddy
     241
     242             v_p(k,-1,i) = v(k,-1,i) + dt_3d * c_v * &
     243                                       ( v(k,-1,i) - v_m_s(k,0,i) ) * ddy
     244
     245             w_p(k,-1,i) = w(k,-1,i) + dt_3d * c_w * &
     246                                       ( w(k,-1,i) - w(k,0,i) ) * ddy
     247
     248!
     249!--          Save old timelevels for the next timestep
     250             u_m_s(k,:,i) = u(k,-1:1,i)
     251             v_m_s(k,:,i) = v(k,-1:1,i)
     252             w_m_s(k,:,i) = w(k,-1:1,i)
     253
     254          ENDDO
     255       ENDDO
     256
     257!
     258!--    Bottom boundary at the outflow
     259       IF ( ibc_uv_b == 0 )  THEN
     260          u_p(nzb,-1,:) = -u_p(nzb+1,-1,:)
     261          v_p(nzb,-1,:) = -v_p(nzb+1,-1,:) 
     262       ELSE                   
     263          u_p(nzb,-1,:) =  u_p(nzb+1,-1,:)
     264          v_p(nzb,-1,:) =  v_p(nzb+1,-1,:)
     265       ENDIF
     266       w_p(nzb,ny+1,:) = 0.0
     267
     268!
     269!--    Top boundary at the outflow
     270       IF ( ibc_uv_t == 0 )  THEN
     271          u_p(nzt+1,-1,:) = ug(nzt+1)
     272          v_p(nzt+1,-1,:) = vg(nzt+1)
     273       ELSE
     274          u_p(nzt+1,-1,:) = u(nzt,-1,:)
     275          v_p(nzt+1,-1,:) = v(nzt,-1,:)
     276       ENDIF
     277       w_p(nzt:nzt+1,-1,:) = 0.0
     278
     279    ENDIF
     280
     281    IF ( outflow_n  .AND.                                                 &
     282         intermediate_timestep_count == intermediate_timestep_count_max ) &
     283    THEN
     284
     285       c_max = dy / dt_3d
     286
     287       DO i = nxl-1, nxr+1
     288          DO k = nzb+1, nzt+1
     289
     290!
     291!--          First calculate the phase speeds for u,v, and w
     292             denom = u_m_n(k,ny,i) - u_m_n(k,ny-1,i)
     293
     294             IF ( denom /= 0.0 )  THEN
     295                c_u = -c_max * ( u(k,ny,i) - u_m_n(k,ny,i) ) / denom
     296                IF ( c_u < 0.0 )  THEN
     297                   c_u = 0.0
     298                ELSEIF ( c_u > c_max )  THEN
    343299                   c_u = c_max
    344300                ENDIF
    345 
    346                 denom = v_m_r(k,j,nx,-2) - v_m_r(k,j,nx-1,-2)
    347 
    348                 IF ( denom /= 0.0 )  THEN
    349                    c_v = -c_max * ( v_m_r(k,j,nx,-1)-v_m_r(k,j,nx,-2) ) / denom
    350                    IF ( c_v < 0.0 )  THEN
    351                       c_v = 0.0
    352                    ELSEIF ( c_v > c_max )  THEN
    353                       c_v = c_max
    354                    ENDIF
    355                 ELSE
     301             ELSE
     302                c_u = c_max
     303             ENDIF
     304
     305             denom = v_m_n(k,ny,i) - v_m_n(k,ny-1,i)
     306
     307             IF ( denom /= 0.0 )  THEN
     308                c_v = -c_max * ( v(k,ny,i) - v_m_n(k,ny,i) ) / denom
     309                IF ( c_v < 0.0 )  THEN
     310                   c_v = 0.0
     311                ELSEIF ( c_v > c_max )  THEN
    356312                   c_v = c_max
    357313                ENDIF
    358 
    359                 denom = w_m_r(k,j,nx,-2) - w_m_r(k,j,nx-1,-2)
    360 
    361                 IF ( denom /= 0.0 )  THEN
    362                    c_w = -c_max * ( w_m_r(k,j,nx,-1)-w_m_n(k,j,nx,-2) ) / denom
    363                    IF ( c_w < 0.0 )  THEN
    364                       c_w = 0.0
    365                    ELSEIF ( c_w > c_max )  THEN
    366                       c_w = c_max
    367                    ENDIF
    368                 ELSE
     314             ELSE
     315                c_v = c_max
     316             ENDIF
     317
     318             denom = w_m_n(k,ny,i) - w_m_n(k,ny-1,i)
     319
     320             IF ( denom /= 0.0 )  THEN
     321                c_w = -c_max * ( w(k,ny,i) - w_m_n(k,ny,i) ) / denom
     322                IF ( c_w < 0.0 )  THEN
     323                   c_w = 0.0
     324                ELSEIF ( c_w > c_max )  THEN
    369325                   c_w = c_max
    370326                ENDIF
    371 
    372 !
    373 !--             Calculate the new velocities
    374                 u(k,j,nx+1) = u_m_r(k,j,nx+1,-1) - dt_3d * c_u * &
    375                               ( u_m_r(k,j,nx+1,-1) - u_m_r(k,j,nx,-1) ) * ddx
    376 
    377                 v(k,j,nx+1) = v_m_r(k,j,nx+1,-1) - dt_3d * c_v * &
    378                               ( v_m_r(k,j,nx+1,-1) - v_m_r(k,j,nx,-1) ) * ddx
    379 
    380                 w(k,j,nx+1) = w_m_r(k,j,nx+1,-1) - dt_3d * c_w * &
    381                               ( w_m_r(k,j,nx+1,-1) - w_m_r(k,j,nx,-1) ) * ddx
    382 
    383 !
    384 !--             Swap timelevels for the next timestep
    385                 u_m_r(k,j,:,-2) = u_m_r(k,j,:,-1)
    386                 u_m_r(k,j,:,-1) = u(k,j,nx-1:nx+1)
    387                 v_m_r(k,j,:,-2) = v_m_r(k,j,:,-1)
    388                 v_m_r(k,j,:,-1) = v(k,j,nx-1:nx+1)
    389                 w_m_r(k,j,:,-2) = w_m_r(k,j,:,-1)
    390                 w_m_r(k,j,:,-1) = w(k,j,nx-1:nx+1)
    391 
    392              ENDDO
    393           ENDDO
    394 
    395 !
    396 !--       Bottom boundary at the outflow
    397           IF ( ibc_uv_b == 0 )  THEN
    398              u(nzb,ny+1,:) = -u(nzb+1,ny+1,:)
    399              v(nzb,ny+1,:) = -v(nzb+1,ny+1,:) 
    400           ELSE                   
    401              u(nzb,ny+1,:) =  u(nzb+1,ny+1,:)
    402              v(nzb,ny+1,:) =  v(nzb+1,ny+1,:)
    403           ENDIF
    404           w(nzb,ny+1,:) = 0.0
    405 
    406 !
    407 !--       Top boundary at the outflow
    408           IF ( ibc_uv_t == 0 )  THEN
    409              u(nzt+1,ny+1,:) = ug(nzt+1)
    410              v(nzt+1,ny+1,:) = vg(nzt+1)
    411           ELSE
    412              u(nzt+1,ny+1,:) = u(nzt,nyn+1,:)
    413              v(nzt+1,ny+1,:) = v(nzt,nyn+1,:)
    414           ENDIF
    415           w(nzt:nzt+1,ny+1,:) = 0.0
    416 
    417        ENDIF
     327             ELSE
     328                c_w = c_max
     329             ENDIF
     330
     331!
     332!--          Calculate the new velocities
     333             u_p(k,ny+1,i) = u(k,ny+1,i) - dt_3d * c_u * &
     334                                           ( u(k,ny+1,i) - u(k,ny,i) ) * ddy
     335
     336             v_p(k,ny+1,i) = v(k,ny+1,i) - dt_3d * c_v * &
     337                                           ( v(k,ny+1,i) - v(k,ny,i) ) * ddy
     338
     339             w_p(k,ny+1,i) = w(k,ny+1,i) - dt_3d * c_w * &
     340                                           ( w(k,ny+1,i) - w(k,ny,i) ) * ddy
     341
     342!
     343!--          Swap timelevels for the next timestep
     344             u_m_n(k,:,i) = u(k,ny-1:ny+1,i)
     345             v_m_n(k,:,i) = v(k,ny-1:ny+1,i)
     346             w_m_n(k,:,i) = w(k,ny-1:ny+1,i)
     347
     348          ENDDO
     349       ENDDO
     350
     351!
     352!--    Bottom boundary at the outflow
     353       IF ( ibc_uv_b == 0 )  THEN
     354          u_p(nzb,ny+1,:) = -u_p(nzb+1,ny+1,:)
     355          v_p(nzb,ny+1,:) = -v_p(nzb+1,ny+1,:) 
     356       ELSE                   
     357          u_p(nzb,ny+1,:) =  u_p(nzb+1,ny+1,:)
     358          v_p(nzb,ny+1,:) =  v_p(nzb+1,ny+1,:)
     359       ENDIF
     360       w_p(nzb,ny+1,:) = 0.0
     361
     362!
     363!--    Top boundary at the outflow
     364       IF ( ibc_uv_t == 0 )  THEN
     365          u_p(nzt+1,ny+1,:) = ug(nzt+1)
     366          v_p(nzt+1,ny+1,:) = vg(nzt+1)
     367       ELSE
     368          u_p(nzt+1,ny+1,:) = u_p(nzt,nyn+1,:)
     369          v_p(nzt+1,ny+1,:) = v_p(nzt,nyn+1,:)
     370       ENDIF
     371       w_p(nzt:nzt+1,ny+1,:) = 0.0
     372
     373    ENDIF
     374
     375    IF ( outflow_l  .AND.                                                 &
     376         intermediate_timestep_count == intermediate_timestep_count_max ) &
     377    THEN
     378
     379       c_max = dx / dt_3d
     380
     381       DO j = nys-1, nyn+1
     382          DO k = nzb+1, nzt+1
     383
     384!
     385!--          First calculate the phase speeds for u,v, and w
     386             denom = u_m_l(k,j,0) - u_m_l(k,j,1)
     387
     388             IF ( denom /= 0.0 )  THEN
     389                c_u = -c_max * ( u(k,j,0) - u_m_r(k,j,0) ) / denom
     390                IF ( c_u > 0.0 )  THEN
     391                   c_u = 0.0
     392                ELSEIF ( c_u < -c_max )  THEN
     393                   c_u = -c_max
     394                ENDIF
     395             ELSE
     396                c_u = -c_max
     397             ENDIF
     398
     399             denom = v_m_l(k,j,0) - v_m_l(k,j,1)
     400
     401             IF ( denom /= 0.0 )  THEN
     402                c_v = -c_max * ( v(k,j,0) - v_m_l(k,j,0) ) / denom
     403                IF ( c_v < 0.0 )  THEN
     404                   c_v = 0.0
     405                ELSEIF ( c_v > c_max )  THEN
     406                   c_v = c_max
     407                ENDIF
     408             ELSE
     409                c_v = c_max
     410             ENDIF
     411
     412             denom = w_m_l(k,j,0) - w_m_l(k,j,1)
     413
     414             IF ( denom /= 0.0 )  THEN
     415                c_w = -c_max * ( w(k,j,0) - w_m_l(k,j,0) ) / denom
     416                IF ( c_w < 0.0 )  THEN
     417                   c_w = 0.0
     418                ELSEIF ( c_w > c_max )  THEN
     419                   c_w = c_max
     420                ENDIF
     421             ELSE
     422                c_w = c_max
     423             ENDIF
     424
     425!
     426!--          Calculate the new velocities
     427             u_p(k,j,-1) = u(k,j,-1) + dt_3d * c_u * &
     428                                       ( u(k,j,-1) - u(k,j,0) ) * ddx
     429
     430             v_p(k,j,-1) = v(k,j,-1) + dt_3d * c_v * &
     431                                       ( v(k,j,-1) - v(k,j,0) ) * ddx
     432
     433             w_p(k,j,-1) = w(k,j,-1) + dt_3d * c_w * &
     434                                       ( w(k,j,-1) - w(k,j,0) ) * ddx
     435
     436!
     437!--          Swap timelevels for the next timestep
     438             u_m_l(k,j,:) = u(k,j,-1:1)
     439             v_m_l(k,j,:) = v(k,j,-1:1)
     440             w_m_l(k,j,:) = w(k,j,-1:1)
     441
     442          ENDDO
     443       ENDDO
     444
     445!
     446!--    Bottom boundary at the outflow
     447       IF ( ibc_uv_b == 0 )  THEN
     448          u_p(nzb,:,-1) = -u_p(nzb+1,:,-1)
     449          v_p(nzb,:,-1) = -v_p(nzb+1,:,-1) 
     450       ELSE                   
     451          u_p(nzb,:,-1) =  u_p(nzb+1,:,-1)
     452          v_p(nzb,:,-1) =  v_p(nzb+1,:,-1)
     453       ENDIF
     454       w_p(nzb,:,-1) = 0.0
     455
     456!
     457!--    Top boundary at the outflow
     458       IF ( ibc_uv_t == 0 )  THEN
     459          u_p(nzt+1,:,-1) = ug(nzt+1)
     460          v_p(nzt+1,:,-1) = vg(nzt+1)
     461       ELSE
     462          u_p(nzt+1,:,-1) = u_p(nzt,:,-1)
     463          v_p(nzt+1,:,-1) = v_p(nzt,:,-1)
     464       ENDIF
     465       w_p(nzt:nzt+1,:,-1) = 0.0
     466
     467    ENDIF
     468
     469    IF ( outflow_r  .AND.                                                 &
     470         intermediate_timestep_count == intermediate_timestep_count_max ) &
     471    THEN
     472
     473       c_max = dx / dt_3d
     474
     475       DO j = nys-1, nyn+1
     476          DO k = nzb+1, nzt+1
     477
     478!
     479!--          First calculate the phase speeds for u,v, and w
     480             denom = u_m_r(k,j,nx) - u_m_r(k,j,nx-1)
     481
     482             IF ( denom /= 0.0 )  THEN
     483                c_u = -c_max * ( u(k,j,nx) - u_m_r(k,j,nx) ) / denom
     484                IF ( c_u < 0.0 )  THEN
     485                   c_u = 0.0
     486                ELSEIF ( c_u > c_max )  THEN
     487                   c_u = c_max
     488                ENDIF
     489             ELSE
     490                c_u = c_max
     491             ENDIF
     492
     493             denom = v_m_r(k,j,nx) - v_m_r(k,j,nx-1)
     494
     495             IF ( denom /= 0.0 )  THEN
     496                c_v = -c_max * ( v(k,j,nx) - v_m_r(k,j,nx) ) / denom
     497                IF ( c_v < 0.0 )  THEN
     498                   c_v = 0.0
     499                ELSEIF ( c_v > c_max )  THEN
     500                   c_v = c_max
     501                ENDIF
     502             ELSE
     503                c_v = c_max
     504             ENDIF
     505
     506             denom = w_m_r(k,j,nx) - w_m_r(k,j,nx-1)
     507
     508             IF ( denom /= 0.0 )  THEN
     509                c_w = -c_max * ( w(k,j,nx) - w_m_r(k,j,nx) ) / denom
     510                IF ( c_w < 0.0 )  THEN
     511                   c_w = 0.0
     512                ELSEIF ( c_w > c_max )  THEN
     513                   c_w = c_max
     514                ENDIF
     515             ELSE
     516                c_w = c_max
     517             ENDIF
     518
     519!
     520!--          Calculate the new velocities
     521             u_p(k,j,nx+1) = u(k,j,nx+1) - dt_3d * c_u * &
     522                                           ( u(k,j,nx+1) - u(k,j,nx) ) * ddx
     523
     524             v_p(k,j,nx+1) = v(k,j,nx+1) - dt_3d * c_v * &
     525                                           ( v(k,j,nx+1) - v(k,j,nx) ) * ddx
     526
     527             w_p(k,j,nx+1) = w(k,j,nx+1) - dt_3d * c_w * &
     528                                           ( w(k,j,nx+1) - w(k,j,nx) ) * ddx
     529
     530!
     531!--          Swap timelevels for the next timestep
     532             u_m_r(k,j,:) = u(k,j,nx-1:nx+1)
     533             v_m_r(k,j,:) = v(k,j,nx-1:nx+1)
     534             w_m_r(k,j,:) = w(k,j,nx-1:nx+1)
     535
     536          ENDDO
     537       ENDDO
     538
     539!
     540!--    Bottom boundary at the outflow
     541       IF ( ibc_uv_b == 0 )  THEN
     542          u_p(nzb,:,nx+1) = -u_p(nzb+1,:,nx+1)
     543          v_p(nzb,:,nx+1) = -v_p(nzb+1,:,nx+1) 
     544       ELSE                   
     545          u_p(nzb,:,nx+1) =  u_p(nzb+1,:,nx+1)
     546          v_p(nzb,:,nx+1) =  v_p(nzb+1,:,nx+1)
     547       ENDIF
     548       w_p(nzb,:,nx+1) = 0.0
     549
     550!
     551!--    Top boundary at the outflow
     552       IF ( ibc_uv_t == 0 )  THEN
     553          u_p(nzt+1,:,nx+1) = ug(nzt+1)
     554          v_p(nzt+1,:,nx+1) = vg(nzt+1)
     555       ELSE
     556          u_p(nzt+1,:,nx+1) = u_p(nzt,:,nx+1)
     557          v_p(nzt+1,:,nx+1) = v_p(nzt,:,nx+1)
     558       ENDIF
     559       w(nzt:nzt+1,:,nx+1) = 0.0
    418560
    419561    ENDIF
  • palm/trunk/SOURCE/check_parameters.f90

    r73 r75  
    66! "by_user" allowed as initializing action, -data_output_ts,
    77! leapfrog with non-flat topography not allowed any more, loop_optimization
    8 ! and pt_reference are checked,
     8! and pt_reference are checked, moisture renamed humidity,
    99! output of precipitation amount/rate and roughnes length + check
    1010! possible negative humidities are avoided in initial profile,
    11 ! dirichlet/neumann changed to dirichlet/radiation, etc.
     11! dirichlet/neumann changed to dirichlet/radiation, etc.,
     12! revision added to run_description_header
    1213!
    1314! Former revisions:
     
    8081    run_time = time(1:2)//':'//time(3:4)//':'//time(5:6)
    8182
    82     WRITE ( run_description_header, '(A,2X,A,A,A,I2.2,2X,A,A,2X,A,1X,A)' )  &
    83               TRIM( version ),'run: ', TRIM( run_identifier ), '.', &
     83    WRITE ( run_description_header, '(A,2X,A,2X,A,A,A,I2.2,2X,A,A,2X,A,1X,A)' )&
     84              TRIM( version ), TRIM( revision ), &
     85              'run: ', TRIM( run_identifier ), '.', &
    8486              runnr, 'host: ', TRIM( host ), run_date, run_time
    8587
     
    131133          WRITE( action, '(A)' )  'cloud_droplets = .TRUE.'
    132134       ENDIF
    133        IF ( moisture )  THEN
    134           WRITE( action, '(A)' )  'moisture = .TRUE.'
     135       IF ( humidity )  THEN
     136          WRITE( action, '(A)' )  'humidity = .TRUE.'
    135137       ENDIF
    136138       IF ( .NOT. prandtl_layer )  THEN
     
    353355    ENDIF
    354356
    355     IF ( cloud_physics  .AND.  .NOT. moisture )  THEN
     357    IF ( cloud_physics  .AND.  .NOT. humidity )  THEN
    356358       IF ( myid == 0 )  PRINT*, '+++ check_parameters: cloud_physics =', &
    357359                                 cloud_physics, ' is not allowed with ',  &
    358                                  'moisture =', moisture
     360                                 'humidity =', humidity
    359361       CALL local_stop
    360362    ENDIF
     
    367369    ENDIF
    368370
    369     IF ( moisture  .AND.  sloping_surface )  THEN
    370        IF ( myid == 0 )  PRINT*, '+++ check_parameters: moisture = TRUE', &
     371    IF ( humidity  .AND.  sloping_surface )  THEN
     372       IF ( myid == 0 )  PRINT*, '+++ check_parameters: humidity = TRUE', &
    371373                                 'and hang = TRUE are not',               &
    372374                                 ' allowed simultaneously'
     
    374376    ENDIF
    375377
    376     IF ( moisture  .AND.  scalar_advec == 'ups-scheme' )  THEN
     378    IF ( humidity  .AND.  scalar_advec == 'ups-scheme' )  THEN
    377379       IF ( myid == 0 )  PRINT*, '+++ check_parameters: UPS-scheme', &
    378                                  'is not implemented for moisture'
     380                                 'is not implemented for humidity'
    379381       CALL local_stop       
    380382    ENDIF
    381383
    382     IF ( passive_scalar  .AND.  moisture )  THEN
    383        IF ( myid == 0 )  PRINT*, '+++ check_parameters: moisture = TRUE and', &
     384    IF ( passive_scalar  .AND.  humidity )  THEN
     385       IF ( myid == 0 )  PRINT*, '+++ check_parameters: humidity = TRUE and', &
    384386                                 'passive_scalar = TRUE is not allowed ',     &
    385387                                 'simultaneously'
     
    410412       v_init  = vg_surface
    411413       pt_init = pt_surface
    412        IF ( moisture )        q_init = q_surface
     414       IF ( humidity )        q_init = q_surface
    413415       IF ( passive_scalar )  q_init = s_surface
    414416
     
    552554       ENDIF
    553555
    554        IF ( moisture  .OR.  passive_scalar )  THEN
     556       IF ( humidity  .OR.  passive_scalar )  THEN
    555557
    556558          i = 1
     
    760762          CALL local_stop
    761763       ENDIF
    762        IF ( conserve_volume_flow )  THEN
    763           IF ( myid == 0 )  THEN
    764              PRINT*, '+++ check_parameters:'
    765              PRINT*, '    non-cyclic lateral boundaries do not allow', &
    766                           ' conserve_volume_flow = .T.'
    767           ENDIF
    768           CALL local_stop
    769        ENDIF
     764!       IF ( conserve_volume_flow )  THEN
     765!          IF ( myid == 0 )  THEN
     766!             PRINT*, '+++ check_parameters:'
     767!             PRINT*, '    non-cyclic lateral boundaries do not allow', &
     768!                          ' conserve_volume_flow = .T.'
     769!          ENDIF
     770!          CALL local_stop
     771!       ENDIF
    770772    ENDIF
    771773
     
    907909
    908910!
    909 !-- In case of moisture or passive scalar, set boundary conditions for total
     911!-- In case of humidity or passive scalar, set boundary conditions for total
    910912!-- water content / scalar
    911     IF ( moisture  .OR.  passive_scalar ) THEN
    912        IF ( moisture )  THEN
     913    IF ( humidity  .OR.  passive_scalar ) THEN
     914       IF ( humidity )  THEN
    913915          sq = 'q'
    914916       ELSE
     
    942944!
    943945!--    A given surface humidity implies Dirichlet boundary condition for
    944 !--    moisture. In this case specification of a constant water flux is
     946!--    humidity. In this case specification of a constant water flux is
    945947!--    forbidden.
    946948       IF ( ibc_q_b == 0  .AND.  constant_waterflux )  THEN
     
    15521554
    15531555          CASE ( 'w"qv"' )
    1554              IF ( moisture  .AND.  .NOT. cloud_physics ) &
     1556             IF ( humidity  .AND.  .NOT. cloud_physics ) &
    15551557             THEN
    15561558                dopr_index(i) = 48
    15571559                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
    1558              ELSEIF( moisture .AND. cloud_physics ) THEN
     1560             ELSEIF( humidity .AND. cloud_physics ) THEN
    15591561                dopr_index(i) = 51
    15601562                hom(:,2,51,:) = SPREAD( zw, 2, statistic_regions+1 )
     
    15641566                           data_output_pr(i),                          &
    15651567                           '    is not implemented for cloud_physics = FALSE', &
    1566                            '    and                    moisture      = FALSE'
     1568                           '    and                    humidity      = FALSE'
    15671569                ENDIF
    15681570                CALL local_stop                   
     
    15701572
    15711573          CASE ( 'w*qv*' )
    1572              IF ( moisture  .AND.  .NOT. cloud_physics ) &
     1574             IF ( humidity  .AND.  .NOT. cloud_physics ) &
    15731575             THEN
    15741576                dopr_index(i) = 49
    15751577                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
    1576              ELSEIF( moisture .AND. cloud_physics ) THEN
     1578             ELSEIF( humidity .AND. cloud_physics ) THEN
    15771579                dopr_index(i) = 52
    15781580                hom(:,2,52,:) = SPREAD( zw, 2, statistic_regions+1 )
     
    15821584                           data_output_pr(i),                                  &
    15831585                           '    is not implemented for cloud_physics = FALSE', &
    1584                            '                       and moisture      = FALSE'
     1586                           '                       and humidity      = FALSE'
    15851587                ENDIF
    15861588                CALL local_stop                   
     
    15881590
    15891591          CASE ( 'wqv' )
    1590              IF ( moisture  .AND.  .NOT. cloud_physics ) &
     1592             IF ( humidity  .AND.  .NOT. cloud_physics ) &
    15911593             THEN
    15921594                dopr_index(i) = 50
    15931595                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
    1594              ELSEIF( moisture .AND. cloud_physics ) THEN
     1596             ELSEIF( humidity .AND. cloud_physics ) THEN
    15951597                dopr_index(i) = 53
    15961598                hom(:,2,53,:) = SPREAD( zw, 2, statistic_regions+1 )
     
    16001602                           data_output_pr(i),                                  &
    16011603                           '    is not implemented for cloud_physics = FALSE', &
    1602                            '                       and moisture      = FALSE'
     1604                           '                       and humidity      = FALSE'
    16031605                ENDIF
    16041606                CALL local_stop                   
     
    18191821
    18201822          CASE ( 'q', 'vpt' )
    1821              IF ( .NOT. moisture )  THEN
     1823             IF ( .NOT. humidity )  THEN
    18221824                IF ( myid == 0 )  THEN
    18231825                   PRINT*, '+++ check_parameters: output of "', TRIM( var ), &
    1824                                 '" requires moisture = .TRUE.'
     1826                                '" requires humidity = .TRUE.'
    18251827                ENDIF
    18261828                CALL local_stop
  • palm/trunk/SOURCE/coriolis.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! uxrp, vynp eliminated
    77!
    88! Former revisions:
     
    5656!--       u-component
    5757          CASE ( 1 )
    58              DO  i = nxl, nxr+uxrp
     58             DO  i = nxl, nxr
    5959                DO  j = nys, nyn
    6060                   DO  k = nzb_u_inner(j,i)+1, nzt
     
    7474          CASE ( 2 )
    7575             DO  i = nxl, nxr
    76                 DO  j = nys, nyn+vynp
     76                DO  j = nys, nyn
    7777                   DO  k = nzb_v_inner(j,i)+1, nzt
    7878                      tend(k,j,i) = tend(k,j,i) - f *     ( 0.25 *          &
  • palm/trunk/SOURCE/data_output_2d.f90

    r72 r75  
    44! Actual revisions:
    55! -----------------
    6 ! Output of precipitation amount/rate and roughness length
     6! Output of precipitation amount/rate and roughness length,
     7! 2nd+3rd argument removed from exchange horiz
    78!
    89! Former revisions:
     
    208209                IF ( av == 0 )  THEN
    209210                   tend = prt_count
    210                    CALL exchange_horiz( tend, 0, 0 )
     211                   CALL exchange_horiz( tend )
    211212                   DO  i = nxl-1, nxr+1
    212213                      DO  j = nys-1, nyn+1
     
    218219                   resorted = .TRUE.
    219220                ELSE
    220                    CALL exchange_horiz( pc_av, 0, 0 )
     221                   CALL exchange_horiz( pc_av )
    221222                   to_be_resorted => pc_av
    222223                ENDIF
     
    243244                      ENDDO
    244245                   ENDDO
    245                    CALL exchange_horiz( tend, 0, 0 )
     246                   CALL exchange_horiz( tend )
    246247                   DO  i = nxl-1, nxr+1
    247248                      DO  j = nys-1, nyn+1
     
    253254                   resorted = .TRUE.
    254255                ELSE
    255                    CALL exchange_horiz( pr_av, 0, 0 )
     256                   CALL exchange_horiz( pr_av )
    256257                   to_be_resorted => pr_av
    257258                ENDIF
  • palm/trunk/SOURCE/data_output_3d.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    129129             IF ( av == 0 )  THEN
    130130                tend = prt_count
    131                 CALL exchange_horiz( tend, 0, 0 )
     131                CALL exchange_horiz( tend )
    132132                DO  i = nxl-1, nxr+1
    133133                   DO  j = nys-1, nyn+1
     
    139139                resorted = .TRUE.
    140140             ELSE
    141                 CALL exchange_horiz( pc_av, 0, 0 )
     141                CALL exchange_horiz( pc_av )
    142142                to_be_resorted => pc_av
    143143             ENDIF
     
    164164                   ENDDO
    165165                ENDDO
    166                 CALL exchange_horiz( tend, 0, 0 )
     166                CALL exchange_horiz( tend )
    167167                DO  i = nxl-1, nxr+1
    168168                   DO  j = nys-1, nyn+1
     
    174174                resorted = .TRUE.
    175175             ELSE
    176                 CALL exchange_horiz( pr_av, 0, 0 )
     176                CALL exchange_horiz( pr_av )
    177177                to_be_resorted => pr_av
    178178             ENDIF
  • palm/trunk/SOURCE/data_output_dvrp.f90

    r60 r75  
    3232! Actual revisions:
    3333! -----------------
    34 ! Particles-package is now part of the default code.
     34! Particles-package is now part of the default code,
     35! moisture renamed humidity
    3536! TEST: write statements
    3637!
     
    391392
    392393             CASE ( 'q', 'q_xy', 'q_xz', 'q_yz' )
    393                 IF ( moisture  .OR.  passive_scalar )  THEN
     394                IF ( humidity  .OR.  passive_scalar )  THEN
    394395                   DO  i = nxl, nxr+1
    395396                      DO  j = nys, nyn+1
     
    401402                ELSE
    402403                   IF ( myid == 0 )  THEN
    403                       PRINT*, '+++ data_output_dvrp: if moisture/passive_scalar = ', &
     404                      PRINT*, '+++ data_output_dvrp: if humidity/passive_scalar = ', &
    404405                              'FALSE output of ', output_variable,            &
    405406                              'is not provided'
  • palm/trunk/SOURCE/diffusion_u.f90

    r57 r75  
    55! -----------------
    66! Wall functions now include diabatic conditions, call of routine wall_fluxes,
    7 ! z0 removed from argument list
     7! z0 removed from argument list, uxrp eliminated
    88!
    99! Former revisions:
     
    6565       REAL, DIMENSION(:,:),   POINTER ::  usws
    6666       REAL, DIMENSION(:,:,:), POINTER ::  km, u, v, w
    67        REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr+uxrp) ::  usvs
     67       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  usvs
    6868
    6969!
     
    7171!--    if neccessary
    7272       IF ( topography /= 'flat' )  THEN
    73           CALL wall_fluxes( usvs, 1.0, 0.0, 0.0, 0.0, uxrp, 0, nzb_u_inner, &
     73          CALL wall_fluxes( usvs, 1.0, 0.0, 0.0, 0.0, nzb_u_inner, &
    7474                            nzb_u_outer, wall_u )
    7575       ENDIF
    7676
    77        DO  i = nxl, nxr+uxrp
     77       DO  i = nxl, nxr
    7878          DO  j = nys,nyn
    7979!
  • palm/trunk/SOURCE/diffusion_v.f90

    r57 r75  
    55! -----------------
    66! Wall functions now include diabatic conditions, call of routine wall_fluxes,
    7 ! z0 removed from argument list
     7! z0 removed from argument list, vynp eliminated
    88!
    99! Former revisions:
     
    6363       REAL, DIMENSION(:,:),   POINTER ::  vsws
    6464       REAL, DIMENSION(:,:,:), POINTER ::  km, u, v, w
    65        REAL, DIMENSION(nzb:nzt+1,nys:nyn+vynp,nxl:nxr) ::  vsus
     65       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  vsus
    6666
    6767!
     
    6969!--    if neccessary
    7070       IF ( topography /= 'flat' )  THEN
    71           CALL wall_fluxes( vsus, 0.0, 1.0, 0.0, 0.0, 0, vynp, nzb_v_inner, &
     71          CALL wall_fluxes( vsus, 0.0, 1.0, 0.0, 0.0, nzb_v_inner, &
    7272                            nzb_v_outer, wall_v )
    7373       ENDIF
    7474
    7575       DO  i = nxl, nxr
    76           DO  j = nys, nyn+vynp
     76          DO  j = nys, nyn
    7777!
    7878!--          Compute horizontal diffusion
  • palm/trunk/SOURCE/diffusion_w.f90

    r57 r75  
    6969!--    walls, if neccessary
    7070       IF ( topography /= 'flat' )  THEN
    71           CALL wall_fluxes( wsus, 0.0, 0.0, 0.0, 1.0, 0, 0, nzb_w_inner, &
     71          CALL wall_fluxes( wsus, 0.0, 0.0, 0.0, 1.0, nzb_w_inner, &
    7272                            nzb_w_outer, wall_w_x )
    73           CALL wall_fluxes( wsvs, 0.0, 0.0, 1.0, 0.0, 0, 0, nzb_w_inner, &
     73          CALL wall_fluxes( wsvs, 0.0, 0.0, 1.0, 0.0, nzb_w_inner, &
    7474                            nzb_w_outer, wall_w_y )
    7575       ENDIF
  • palm/trunk/SOURCE/disturb_field.f90

    r4 r75  
    1  SUBROUTINE disturb_field( nzb_uv_inner, dist1, field, xrp, ynp )
     1 SUBROUTINE disturb_field( nzb_uv_inner, dist1, field )
    22
    33!------------------------------------------------------------------------------!
    44! Actual revisions:
    55! -----------------
    6 !
     6! xrp, ynp eliminated, 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    3636    IMPLICIT NONE
    3737
    38     INTEGER ::  i, j, k, xrp, ynp
     38    INTEGER ::  i, j, k
    3939    INTEGER ::  nzb_uv_inner(nys-1:nyn+1,nxl-1:nxr+1)
    4040
    4141    REAL    ::  randomnumber,                             &
    4242                dist1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
    43                 field(nzb:nzt+1,nys-1:nyn+ynp+1,nxl-1:nxr+xrp+1)
     43                field(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
    4444    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  dist2
    4545
     
    9494!
    9595!-- Exchange of ghost points for the random perturbation
    96     CALL exchange_horiz( dist1, 0, 0 )
     96    CALL exchange_horiz( dist1 )
    9797
    9898!
     
    114114!-- Exchange of ghost points for the filtered perturbation.
    115115!-- Afterwards, filter operation and exchange of ghost points are repeated.
    116     CALL exchange_horiz( dist2, 0, 0 )
     116    CALL exchange_horiz( dist2 )
    117117    DO  i = nxl, nxr
    118118       DO  j = nys, nyn
     
    125125       ENDDO
    126126    ENDDO
    127     CALL exchange_horiz( dist1, 0, 0 )
     127    CALL exchange_horiz( dist1 )
    128128
    129129!
  • palm/trunk/SOURCE/exchange_horiz.f90

    r4 r75  
    1  SUBROUTINE exchange_horiz( ar, xrp, ynp )
     1 SUBROUTINE exchange_horiz( ar )
    22
    33!------------------------------------------------------------------------------!
    44! Actual revisions:
    55! -----------------
    6 !
     6! Special cases for additional gridpoints along x or y in case of non-cyclic
     7! boundary conditions are not regarded any more
    78!
    89! Former revisions:
     
    3233    IMPLICIT NONE
    3334
    34     INTEGER ::  xrp, ynp
    35 
    3635#if defined( __parallel )
    37     INTEGER                               ::  typexz
    3836    INTEGER, DIMENSION(4)                 ::  req
    3937    INTEGER, DIMENSION(MPI_STATUS_SIZE,4) ::  wait_stat
    4038#endif
    4139
    42     REAL ::  ar(nzb:nzt+1,nys-1:nyn+ynp+1,nxl-1:nxr+xrp+1)
     40    REAL ::  ar(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
    4341
    4442
     
    5957
    6058    ELSE
     59
    6160       req = 0
    6261!
     
    7675               ar(nzb,nys-1,nxl-1), ngp_yz(grid_level), MPI_REAL, pleft,  1, &
    7776                          comm2d, req(4), ierr )
    78        call MPI_Waitall (4,req,wait_stat,ierr)
     77       CALL MPI_WAITALL( 4, req, wait_stat, ierr )
     78
    7979    ENDIF
    8080
     
    9090
    9191    ELSE
    92 !
    93 !--    Set the MPI data type, which depends on the size of the array
    94 !--    (the v array has an additional gridpoint along y in case of non-cyclic
    95 !--    boundary conditions)
    96        IF ( ynp == 0 )  THEN
    97           typexz = type_xz(grid_level)
    98        ELSE
    99           typexz = type_xz_p
    100        ENDIF
    10192
    10293       req = 0
    10394!
    10495!--    Send front boundary, receive rear one
    105        CALL MPI_ISEND( ar(nzb,nys,nxl-1),   1, typexz, psouth, 0, comm2d, &
    106                        req(1), ierr )
    107        CALL MPI_IRECV( ar(nzb,nyn+1,nxl-1), 1, typexz, pnorth, 0, comm2d, &
    108                        req(2), ierr )
     96       CALL MPI_ISEND( ar(nzb,nys,nxl-1),   1, type_xz(grid_level), psouth, 0, &
     97                       comm2d, req(1), ierr )
     98       CALL MPI_IRECV( ar(nzb,nyn+1,nxl-1), 1, type_xz(grid_level), pnorth, 0, &
     99                       comm2d, req(2), ierr )
    109100!
    110101!--    Send rear boundary, receive front one
    111        CALL MPI_ISEND( ar(nzb,nyn,nxl-1),   1, typexz, pnorth, 1, comm2d, &
    112                        req(3), ierr )
    113        CALL MPI_IRECV( ar(nzb,nys-1,nxl-1), 1, typexz, psouth, 1, comm2d, &
    114                        req(4), ierr )
    115        call MPI_Waitall (4,req,wait_stat,ierr)
     102       CALL MPI_ISEND( ar(nzb,nyn,nxl-1),   1, type_xz(grid_level), pnorth, 1, &
     103                       comm2d, req(3), ierr )
     104       CALL MPI_IRECV( ar(nzb,nys-1,nxl-1), 1, type_xz(grid_level), psouth, 1, &
     105                       comm2d, req(4), ierr )
     106       call MPI_WAITALL( 4, req, wait_stat, ierr )
     107
    116108    ENDIF
    117109
  • palm/trunk/SOURCE/flow_statistics.f90

    r51 r75  
    55! -----------------
    66! Collection of time series quantities moved from routine flow_statistics to
    7 ! here, routine user_statistics is called for each statistic region
     7! here, routine user_statistics is called for each statistic region,
     8! moisture renamed humidity
    89!
    910! Former revisions:
     
    115116!--    total water content, specific humidity and liquid water potential
    116117!--    temperature
    117        IF ( moisture )  THEN
     118       IF ( humidity )  THEN
    118119          !$OMP DO
    119120          DO  i = nxl, nxr
     
    164165             sums_l(:,2,0) = sums_l(:,2,0) + sums_l(:,2,i)
    165166             sums_l(:,4,0) = sums_l(:,4,0) + sums_l(:,4,i)
    166              IF ( moisture )  THEN
     167             IF ( humidity )  THEN
    167168                sums_l(:,41,0) = sums_l(:,41,0) + sums_l(:,41,i)
    168169                sums_l(:,44,0) = sums_l(:,44,0) + sums_l(:,44,i)
     
    187188       CALL MPI_ALLREDUCE( sums_l(nzb,4,0), sums(nzb,4), nzt+2-nzb, MPI_REAL, &
    188189                           MPI_SUM, comm2d, ierr )
    189        IF ( moisture ) THEN
     190       IF ( humidity ) THEN
    190191          CALL MPI_ALLREDUCE( sums_l(nzb,44,0), sums(nzb,44), nzt+2-nzb, &
    191192                              MPI_REAL, MPI_SUM, comm2d, ierr )
     
    208209       sums(:,2) = sums_l(:,2,0)
    209210       sums(:,4) = sums_l(:,4,0)
    210        IF ( moisture ) THEN
     211       IF ( humidity ) THEN
    211212          sums(:,44) = sums_l(:,44,0)
    212213          sums(:,41) = sums_l(:,41,0)
     
    231232!
    232233!--    Humidity and cloud parameters
    233        IF ( moisture ) THEN
     234       IF ( humidity ) THEN
    234235          sums(:,44) = sums(:,44) / ngp_2dh_outer(:,sr)
    235236          sums(:,41) = sums(:,41) / ngp_2dh_outer(:,sr)
     
    365366!
    366367!--             Buoyancy flux, water flux (humidity flux) w"q"
    367                 IF ( moisture ) THEN
     368                IF ( humidity ) THEN
    368369                   sums_l(k,45,tn) = sums_l(k,45,tn)                           &
    369370                                         - 0.5 * ( kh(k,j,i) + kh(k+1,j,i) )   &
     
    407408                sums_l(nzb,61,tn) = sums_l(nzb,61,tn) + &
    408409                                    0.0 * rmask(j,i,sr)           ! v"pt"
    409                 IF ( moisture )  THEN
     410                IF ( humidity )  THEN
    410411                   sums_l(nzb,48,tn) = sums_l(nzb,48,tn) + &
    411412                                       qsws(j,i) * rmask(j,i,sr)  ! w"q" (w"qv")
     
    437438                sums_l(nzt,61,tn) = sums_l(nzt,61,tn) + &
    438439                                    0.0 * rmask(j,i,sr)           ! v"pt"
    439                 IF ( moisture )  THEN
     440                IF ( humidity )  THEN
    440441                   sums_l(nzt,48,tn) = sums_l(nzt,48,tn) + &
    441442                                       qswst(j,i) * rmask(j,i,sr)  ! w"q" (w"qv")
     
    499500!--             Buoyancy flux, water flux, humidity flux and liquid water
    500501!--             content
    501                 IF ( moisture )  THEN
     502                IF ( humidity )  THEN
    502503                   pts = 0.5 * ( vpt(k,j,i)   - hom(k,1,44,sr) + &
    503504                                 vpt(k+1,j,i) - hom(k+1,1,44,sr) )
  • palm/trunk/SOURCE/header.f90

    r63 r75  
    55! -----------------
    66! Output of netcdf_64bit_3d, particles-package is now part of the default code,
    7 ! output of the loop optimization method.
     7! output of the loop optimization method, moisture renamed humidity,
     8! output of subversion revision number
    89!
    910! Former revisions:
     
    5253    CHARACTER (LEN=10) ::  coor_chr, host_chr
    5354    CHARACTER (LEN=16) ::  begin_chr
     55    CHARACTER (LEN=21) ::  ver_rev
    5456    CHARACTER (LEN=40) ::  output_format
    5557    CHARACTER (LEN=70) ::  char1, char2, coordinates, gradients, dopr_chr, &
     
    9597!-- Run-identification, date, time, host
    9698    host_chr = host(1:10)
    97     WRITE ( io, 100 )  version, TRIM( run_classification ), run_date, &
     99    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
     100    WRITE ( io, 100 )  ver_rev, TRIM( run_classification ), run_date, &
    98101                       run_identifier, run_time, runnr, ADJUSTR( host_chr )
    99102#if defined( __parallel )
     
    217220       WRITE ( io, 123 )  rayleigh_damping_height, rayleigh_damping_factor
    218221    ENDIF
    219     IF ( moisture )  THEN
     222    IF ( humidity )  THEN
    220223       IF ( .NOT. cloud_physics )  THEN
    221224          WRITE ( io, 129 )
     
    370373    ENDIF
    371374
    372     IF ( moisture  .OR.  passive_scalar )  THEN
    373        IF ( moisture )  THEN
     375    IF ( humidity  .OR.  passive_scalar )  THEN
     376       IF ( humidity )  THEN
    374377          IF ( ibc_q_b == 0 )  THEN
    375378             runten = 'q(0)     = q_surface'
     
    405408          IF ( random_heatflux )  WRITE ( io, 307 )
    406409       ENDIF
    407        IF ( moisture  .AND.  constant_waterflux )  THEN
     410       IF ( humidity  .AND.  constant_waterflux )  THEN
    408411          WRITE ( io, 311 ) surface_waterflux
    409412       ENDIF
     
    418421          WRITE ( io, 306 )  top_heatflux
    419422       ENDIF
    420        IF ( moisture  .OR.  passive_scalar )  THEN
     423       IF ( humidity  .OR.  passive_scalar )  THEN
    421424          WRITE ( io, 315 )
    422425       ENDIF
     
    426429       WRITE ( io, 305 )  zu(1), roughness_length, kappa, rif_min, rif_max
    427430       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
    428        IF ( moisture  .AND.  .NOT. constant_waterflux )  THEN
     431       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
    429432          WRITE ( io, 312 )
    430433       ENDIF
     
    955958!-- Initial humidity profile
    956959!-- Building output strings, starting with surface humidity
    957     IF ( moisture  .OR.  passive_scalar )  THEN
     960    IF ( humidity  .OR.  passive_scalar )  THEN
    958961       WRITE ( temperatures, '(E8.1)' )  q_surface
    959962       gradients = '--------'
     
    978981       ENDDO
    979982
    980        IF ( moisture )  THEN
     983       IF ( humidity )  THEN
    981984          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
    982985                             TRIM( gradients ), TRIM( slices )
     
    10211024       WRITE ( io, 475 )  pt_surface_initial_change
    10221025    ENDIF
    1023     IF ( moisture  .AND.  q_surface_initial_change /= 0.0 )  THEN
     1026    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
    10241027       WRITE ( io, 476 )  q_surface_initial_change       
    10251028    ENDIF
     
    11131116
    11141117 99 FORMAT (1X,78('-'))
    1115 100 FORMAT (/10X,'****************',11X,28('-')/                &
    1116             10X,'*  ',A12,'*',11X,A/                            &
    1117             10X,'****************',11X,28('-')//                &
     1118100 FORMAT (/1X,'*************************',11X,28('-')/        &
     1119            1X,'* ',A,' *',11X,A/                               &
     1120            1X,'*************************',11X,28('-')//        &
    11181121            ' Date:            ',A8,11X,'Run:       ',A20/      &
    11191122            ' Time:            ',A8,11X,'Run-No.:   ',I2.2/     &
  • palm/trunk/SOURCE/init_1d_model.f90

    r46 r75  
    44! Actual revisions:
    55! -----------------
    6 ! Bugfix: preset of tendencies te_em, te_um, te_vm
     6! Bugfix: preset of tendencies te_em, te_um, te_vm,
     7! moisture renamed humidity
    78!
    89! Former revisions:
     
    125126    vsws1d = 0.0; vsws1d_m = 0.0
    126127    z01d = roughness_length
    127     IF ( moisture .OR. passive_scalar )  qs1d = 0.0
     128    IF ( humidity .OR. passive_scalar )  qs1d = 0.0
    128129
    129130!
     
    216217                kmzm = 0.5 * ( km1d_m(k-1) + km1d_m(k) )
    217218                kmzp = 0.5 * ( km1d_m(k) + km1d_m(k+1) )
    218                 IF ( .NOT. moisture )  THEN
     219                IF ( .NOT. humidity )  THEN
    219220                   pt_0 = pt_init(k)
    220221                   flux =  ( pt_init(k+1)-pt_init(k-1) ) * dd2zu(k)
     
    256257             kmzm = 0.5 * ( km1d_m(k-1) + km1d_m(k) )
    257258             kmzp = 0.5 * ( km1d_m(k) + km1d_m(k+1) )
    258              IF ( .NOT. moisture )  THEN
     259             IF ( .NOT. humidity )  THEN
    259260                pt_0 = pt_init(k)
    260261                flux =  ( pt_init(k+1)-pt_init(k-1) ) * dd2zu(k)
     
    450451
    451452             IF ( prandtl_layer )  THEN
    452                 IF ( .NOT. moisture )  THEN
     453                IF ( .NOT. humidity )  THEN
    453454                   pt_0 = pt_init(nzb+1)
    454455                   flux = ts1d
     
    462463
    463464             DO  k = nzb_diff, nzt
    464                 IF ( .NOT. moisture )  THEN
     465                IF ( .NOT. humidity )  THEN
    465466                   pt_0 = pt_init(k)
    466467                   flux = ( pt_init(k+1) - pt_init(k-1) ) * dd2zu(k)
     
    544545                e1d(nzb) = e1d(nzb+1)
    545546
    546                 IF ( moisture .OR. passive_scalar ) THEN
     547                IF ( humidity .OR. passive_scalar ) THEN
    547548!
    548549!--                Compute q*
  • palm/trunk/SOURCE/init_3d_model.f90

    r73 r75  
    99! Arrays for radiation boundary conditions are allocated (u_m_l, u_m_r, etc.),
    1010! bugfix for cases with the outflow damping layer extending over more than one
    11 ! subdomain,
    12 ! New initializing action "by_user" calls user_init_3d_model,
     11! subdomain, moisture renamed humidity,
     12! new initializing action "by_user" calls user_init_3d_model,
    1313! precipitation_amount/rate, ts_value are allocated, +module netcdf_control,
    1414! initial velocities at nzb+1 are regarded for volume
    1515! flow control in case they have been set zero before (to avoid small timesteps)
     16! -uvmean_outflow, uxrp, vynp eliminated
    1617!
    1718! Former revisions:
     
    7677              sums_divnew_l(0:statistic_regions),                           &
    7778              sums_divold_l(0:statistic_regions) )
    78     ALLOCATE( rdf(nzb+1:nzt), uvmean_outflow(nzb:nzt+1),                    &
    79               uvmean_outflow_l(nzb:nzt+1) )
     79    ALLOCATE( rdf(nzb+1:nzt) )
    8080    ALLOCATE( hom_sum(nzb:nzt+1,var_hom,0:statistic_regions),               &
    8181              ngp_2dh_outer(nzb:nzt+1,0:statistic_regions),                 &
     
    105105    ENDIF
    106106
    107     ALLOCATE( d(nzb+1:nzta,nys:nyna,nxl:nxra),             &
    108               e_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),      &
    109               e_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),      &
    110               e_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),      &
    111               kh_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    112               km_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    113               p(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),        &
    114               pt_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    115               pt_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    116               pt_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    117               tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),     &
    118               u_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1+uxrp), &
    119               u_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1+uxrp), &
    120               u_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1+uxrp), &
    121               v_1(nzb:nzt+1,nys-1:nyn+1+vynp,nxl-1:nxr+1), &
    122               v_2(nzb:nzt+1,nys-1:nyn+1+vynp,nxl-1:nxr+1), &
    123               v_3(nzb:nzt+1,nys-1:nyn+1+vynp,nxl-1:nxr+1), &
    124               w_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),      &
    125               w_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),      &
     107    ALLOCATE( d(nzb+1:nzta,nys:nyna,nxl:nxra),         &
     108              e_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),  &
     109              e_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),  &
     110              e_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),  &
     111              kh_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     112              km_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     113              p(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),    &
     114              pt_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     115              pt_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     116              pt_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     117              tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     118              u_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     119              u_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     120              u_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     121              v_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     122              v_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     123              v_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     124              w_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),  &
     125              w_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1),  &
    126126              w_3(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
    127127
     
    131131    ENDIF
    132132
    133     IF ( moisture  .OR.  passive_scalar ) THEN
    134 !
    135 !--    2D-moisture/scalar arrays
     133    IF ( humidity  .OR.  passive_scalar ) THEN
     134!
     135!--    2D-humidity/scalar arrays
    136136       ALLOCATE ( qs(nys-1:nyn+1,nxl-1:nxr+1),     &
    137137                  qsws_1(nys-1:nyn+1,nxl-1:nxr+1), &
     
    143143       ENDIF
    144144!
    145 !--    3D-moisture/scalar arrays
     145!--    3D-humidity/scalar arrays
    146146       ALLOCATE( q_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
    147147                 q_2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
     
    149149
    150150!
    151 !--    3D-arrays needed for moisture only
    152        IF ( moisture )  THEN
     151!--    3D-arrays needed for humidity only
     152       IF ( humidity )  THEN
    153153          ALLOCATE( vpt_1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
    154154
     
    212212!-- conditions
    213213    IF ( outflow_l )  THEN
    214        ALLOCATE( u_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1,-2:-1), &
    215                  v_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1,-2:-1), &
    216                  w_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1,-2:-1) )
     214       ALLOCATE( u_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1), &
     215                 v_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1), &
     216                 w_m_l(nzb:nzt+1,nys-1:nyn+1,-1:1) )
    217217    ENDIF
    218218    IF ( outflow_r )  THEN
    219        ALLOCATE( u_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1,-2:-1), &
    220                  v_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1,-2:-1), &
    221                  w_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1,-2:-1) )
     219       ALLOCATE( u_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1), &
     220                 v_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1), &
     221                 w_m_r(nzb:nzt+1,nys-1:nyn+1,nx-1:nx+1) )
    222222    ENDIF
    223223    IF ( outflow_s )  THEN
    224        ALLOCATE( u_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1,-2:-1), &
    225                  v_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1,-2:-1), &
    226                  w_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1,-2:-1) )
     224       ALLOCATE( u_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1), &
     225                 v_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1), &
     226                 w_m_s(nzb:nzt+1,-1:1,nxl-1:nxr+1) )
    227227    ENDIF
    228228    IF ( outflow_n )  THEN
    229        ALLOCATE( u_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1,-2:-1), &
    230                  v_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1,-2:-1), &
    231                  w_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1,-2:-1) )
     229       ALLOCATE( u_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1), &
     230                 v_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1), &
     231                 w_m_n(nzb:nzt+1,ny-1:ny+1,nxl-1:nxr+1) )
    232232    ENDIF
    233233
     
    249249       w_m  => w_1;   w  => w_2;   w_p  => w_3;   tw_m  => w_3
    250250
    251        IF ( moisture  .OR.  passive_scalar )  THEN
     251       IF ( humidity  .OR.  passive_scalar )  THEN
    252252          qsws_m  => qsws_1;   qsws  => qsws_2
    253253          qswst_m => qswst_1;  qswst => qswst_2
    254254          q_m    => q_1;     q    => q_2;     q_p => q_3;     tq_m => q_3
    255           IF ( moisture )        vpt_m  => vpt_1;   vpt  => vpt_2
     255          IF ( humidity )        vpt_m  => vpt_1;   vpt  => vpt_2
    256256          IF ( cloud_physics )   ql   => ql_1
    257257          IF ( cloud_droplets )  THEN
     
    276276       w     => w_1;   w_p  => w_2;   tw_m  => w_3;   w_m  => w_3
    277277
    278        IF ( moisture  .OR.  passive_scalar )  THEN
     278       IF ( humidity  .OR.  passive_scalar )  THEN
    279279          qsws   => qsws_1
    280280          qswst  => qswst_1
    281281          q      => q_1;     q_p  => q_2;     tq_m => q_3;    q_m => q_3
    282           IF ( moisture )        vpt  => vpt_1
     282          IF ( humidity )        vpt  => vpt_1
    283283          IF ( cloud_physics )   ql   => ql_1
    284284          IF ( cloud_droplets )  THEN
     
    309309                km(:,j,i) = km1d
    310310                pt(:,j,i) = pt_init
    311              ENDDO
    312           ENDDO
    313           DO  i = nxl-1, nxr+uxrp+1
    314              DO  j = nys-1, nyn+1
    315311                u(:,j,i)  = u1d
    316              ENDDO
    317           ENDDO
    318           DO  i = nxl-1, nxr+1
    319              DO  j = nys-1, nyn+vynp+1
    320312                v(:,j,i)  = v1d
    321313             ENDDO
    322314          ENDDO
    323315
    324           IF ( moisture  .OR.  passive_scalar )  THEN
     316          IF ( humidity  .OR.  passive_scalar )  THEN
    325317             DO  i = nxl-1, nxr+1
    326318                DO  j = nys-1, nyn+1
     
    368360!--       This could actually be computed more accurately in the 1D model.
    369361!--       Update when opportunity arises!
    370           IF ( moisture  .OR.  passive_scalar )  qs = 0.0
     362          IF ( humidity  .OR.  passive_scalar )  qs = 0.0
    371363
    372364!
     
    419411             DO  j = nys-1, nyn+1
    420412                pt(:,j,i) = pt_init
    421              ENDDO
    422           ENDDO
    423           DO  i = nxl-1, nxr+uxrp+1
    424              DO  j = nys-1, nyn+1
    425413                u(:,j,i)  = u_init
    426              ENDDO
    427           ENDDO
    428           DO  i = nxl-1, nxr+1
    429              DO  j = nys-1, nyn+vynp+1
    430414                v(:,j,i)  = v_init
    431415             ENDDO
    432416          ENDDO
     417
    433418!
    434419!--       Set initial horizontal velocities at the lowest computational grid levels
     
    458443          ENDIF
    459444
    460           IF ( moisture  .OR.  passive_scalar )  THEN
     445          IF ( humidity  .OR.  passive_scalar )  THEN
    461446             DO  i = nxl-1, nxr+1
    462447                DO  j = nys-1, nyn+1
     
    482467          usws = 0.0
    483468          vsws = 0.0
    484           IF ( moisture  .OR.  passive_scalar ) qs = 0.0
     469          IF ( humidity  .OR.  passive_scalar ) qs = 0.0
    485470
    486471!
     
    499484!
    500485!--    Calculate virtual potential temperature
    501        IF ( moisture ) vpt = pt * ( 1.0 + 0.61 * q )
     486       IF ( humidity ) vpt = pt * ( 1.0 + 0.61 * q )
    502487
    503488!
     
    515500
    516501
    517        IF ( moisture )  THEN
     502       IF ( humidity )  THEN
    518503!
    519504!--       Store initial profile of total water content, virtual potential
     
    564549!
    565550!--       Determine the near-surface water flux
    566           IF ( moisture  .OR.  passive_scalar )  THEN
     551          IF ( humidity  .OR.  passive_scalar )  THEN
    567552             IF ( constant_waterflux )  THEN
    568553                qsws   = surface_waterflux
     
    585570             IF ( ASSOCIATED( tswst_m ) )  tswst_m = tswst
    586571
    587              IF ( moisture  .OR.  passive_scalar )  THEN
     572             IF ( humidity  .OR.  passive_scalar )  THEN
    588573                qswst = 0.0
    589574                IF ( ASSOCIATED( qswst_m ) )  qswst_m = qswst
     
    610595          ENDIF
    611596
    612           IF ( moisture  .OR.  passive_scalar )  THEN
     597          IF ( humidity  .OR.  passive_scalar )  THEN
    613598             IF ( .NOT. constant_waterflux )  THEN
    614599                qsws   = 0.0
     
    709694!--    If required, change the surface humidity/scalar at the start of the 3D
    710695!--    run
    711        IF ( ( moisture .OR. passive_scalar ) .AND. &
     696       IF ( ( humidity .OR. passive_scalar ) .AND. &
    712697            q_surface_initial_change /= 0.0 )  THEN
    713698          q(nzb,:,:) = q(nzb,:,:) + q_surface_initial_change
     
    722707!--    remove the divergences from the velocity field
    723708       IF ( create_disturbances )  THEN
    724           CALL disturb_field( nzb_u_inner, tend, u, uxrp,    0 )
    725           CALL disturb_field( nzb_v_inner, tend, v,    0, vynp )
     709          CALL disturb_field( nzb_u_inner, tend, u )
     710          CALL disturb_field( nzb_v_inner, tend, v )
    726711          n_sor = nsor_ini
    727712          CALL pres
     
    746731       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    747732
    748        IF ( moisture  .OR.  passive_scalar )  THEN
     733       IF ( humidity  .OR.  passive_scalar )  THEN
    749734          IF ( ASSOCIATED( q_m ) )  q_m = q
    750735          IF ( timestep_scheme(1:5) == 'runge' )  tq_m = 0.0
    751736          q_p = q
    752           IF ( moisture  .AND.  ASSOCIATED( vpt_m ) )  vpt_m = vpt
     737          IF ( humidity  .AND.  ASSOCIATED( vpt_m ) )  vpt_m = vpt
    753738       ENDIF
    754739
     
    756741!--    Initialize old timelevels needed for radiation boundary conditions
    757742       IF ( outflow_l )  THEN
    758           u_m_l(:,:,:,-2) = u(:,:,-1:1)
    759           v_m_l(:,:,:,-2) = v(:,:,-1:1)
    760           w_m_l(:,:,:,-2) = w(:,:,-1:1)
    761           u_m_l(:,:,:,-1) = u(:,:,-1:1)
    762           v_m_l(:,:,:,-1) = v(:,:,-1:1)
    763           w_m_l(:,:,:,-1) = w(:,:,-1:1)
     743          u_m_l(:,:,:) = u(:,:,-1:1)
     744          v_m_l(:,:,:) = v(:,:,-1:1)
     745          w_m_l(:,:,:) = w(:,:,-1:1)
    764746       ENDIF
    765747       IF ( outflow_r )  THEN
    766           u_m_r(:,:,:,-2) = u(:,:,nx-1:nx+1)
    767           v_m_r(:,:,:,-2) = v(:,:,nx-1:nx+1)
    768           w_m_r(:,:,:,-2) = w(:,:,nx-1:nx+1)
    769           u_m_r(:,:,:,-1) = u(:,:,nx-1:nx+1)
    770           v_m_r(:,:,:,-1) = v(:,:,nx-1:nx+1)
    771           w_m_r(:,:,:,-1) = w(:,:,nx-1:nx+1)
     748          u_m_r(:,:,:) = u(:,:,nx-1:nx+1)
     749          v_m_r(:,:,:) = v(:,:,nx-1:nx+1)
     750          w_m_r(:,:,:) = w(:,:,nx-1:nx+1)
    772751       ENDIF
    773752       IF ( outflow_s )  THEN
    774           u_m_s(:,:,:,-2) = u(:,-1:1,:)
    775           v_m_s(:,:,:,-2) = v(:,-1:1,:)
    776           w_m_s(:,:,:,-2) = w(:,-1:1,:)
    777           u_m_s(:,:,:,-1) = u(:,-1:1,:)
    778           v_m_s(:,:,:,-1) = v(:,-1:1,:)
    779           w_m_s(:,:,:,-1) = w(:,-1:1,:)
     753          u_m_s(:,:,:) = u(:,-1:1,:)
     754          v_m_s(:,:,:) = v(:,-1:1,:)
     755          w_m_s(:,:,:) = w(:,-1:1,:)
    780756       ENDIF
    781757       IF ( outflow_n )  THEN
    782           u_m_n(:,:,:,-2) = u(:,ny-1:ny+1,:)
    783           v_m_n(:,:,:,-2) = v(:,ny-1:ny+1,:)
    784           w_m_n(:,:,:,-2) = w(:,ny-1:ny+1,:)
    785           u_m_n(:,:,:,-1) = u(:,ny-1:ny+1,:)
    786           v_m_n(:,:,:,-1) = v(:,ny-1:ny+1,:)
    787           w_m_n(:,:,:,-1) = w(:,ny-1:ny+1,:)
     758          u_m_n(:,:,:) = u(:,ny-1:ny+1,:)
     759          v_m_n(:,:,:) = v(:,ny-1:ny+1,:)
     760          w_m_n(:,:,:) = w(:,ny-1:ny+1,:)
    788761       ENDIF
    789762
     
    803776!--    including ghost points)
    804777       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    805        IF ( moisture  .OR.  passive_scalar )  q_p = q
     778       IF ( humidity  .OR.  passive_scalar )  q_p = q
    806779
    807780    ELSE
  • palm/trunk/SOURCE/init_grid.f90

    r49 r75  
    44! Actual revisions:
    55! -----------------
    6 ! storage of topography height arrays zu_s_inner and zw_s_inner
     6! storage of topography height arrays zu_s_inner and zw_s_inner,
     7! 2nd+3rd argument removed from exchange horiz
    78!
    89! Former revisions:
     
    823824!
    824825!-- Need to set lateral boundary conditions for l_wall
    825     CALL exchange_horiz( l_wall, 0, 0 )
     826    CALL exchange_horiz( l_wall )
    826827
    827828    DEALLOCATE( corner_nl, corner_nr, corner_sl, corner_sr, nzb_local, &
  • palm/trunk/SOURCE/init_pegrid.f90

    r73 r75  
    55! -----------------
    66! uxrp, vynp eliminated,
    7 ! dirichlet/neumann changed to dirichlet/radiation, etc.
     7! dirichlet/neumann changed to dirichlet/radiation, etc.,
     8! poisfft_init is only called if fft-solver is switched on
    89!
    910! Former revisions:
     
    493494    nzta = nz
    494495    nnz  = nz
    495 
    496 !
    497 !-- For non-cyclic boundaries extend array u (v) by one gridpoint
    498 !    IF ( bc_lr /= 'cyclic' )  uxrp = 1
    499 !    IF ( bc_ns /= 'cyclic' )  vynp = 1
    500496
    501497!
     
    757753          inflow_r  = .TRUE.
    758754       ENDIF
    759 !       uxrp      = 1
    760755    ENDIF
    761756
     
    774769          outflow_n = .TRUE.
    775770       ENDIF
    776 !       vynp      = 1
    777     ENDIF
    778 
    779 !
    780 !-- Additional MPI derived data type for the exchange of ghost points along x
    781 !-- needed in case of non-cyclic boundary conditions along y on the northmost
    782 !-- processors (for the exchange of the enlarged v array)
    783     IF ( bc_ns /= 'cyclic'  .AND.  pnorth == MPI_PROC_NULL )  THEN
    784        ngp_yz_p = ( nzt - nzb + 2 ) * ( nyn + vynp - nys + 3 )
    785        CALL MPI_TYPE_VECTOR( nxr-nxl+3, nzt-nzb+2, ngp_yz_p, &
    786                              MPI_REAL, type_xz_p, ierr )
    787        CALL MPI_TYPE_COMMIT( type_xz_p, ierr )
    788     ENDIF
     771    ENDIF
     772
    789773#else
    790774    IF ( bc_lr == 'dirichlet/radiation' )  THEN
    791775       inflow_l  = .TRUE.
    792776       outflow_r = .TRUE.
    793 !       uxrp      = 1
    794777    ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
    795778       outflow_l = .TRUE.
     
    803786       outflow_n = .TRUE.
    804787       inflow_s  = .TRUE.
    805 !       vynp      = 1
    806788    ENDIF
    807789#endif
     
    809791    IF ( psolver == 'poisfft_hybrid' )  THEN
    810792       CALL poisfft_hybrid_ini
    811     ELSE
     793    ELSEIF ( psolver == 'poisfft' )  THEN
    812794       CALL poisfft_init
    813795    ENDIF
  • palm/trunk/SOURCE/init_pt_anomaly.f90

    r39 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    7070!
    7171!-- Exchange of boundary values for temperature
    72     CALL exchange_horiz( pt, 0, 0 )
     72    CALL exchange_horiz( pt )
    7373
    7474
  • palm/trunk/SOURCE/init_rankine.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    129129!
    130130!-- Exchange of boundary values for the velocities.
    131     CALL exchange_horiz( u, uxrp,    0 )
    132     CALL exchange_horiz( v,    0, vynp )
     131    CALL exchange_horiz( u )
     132    CALL exchange_horiz( v )
    133133!
    134134!-- Make velocity field nondivergent.
  • palm/trunk/SOURCE/modules.f90

    r73 r75  
    99! +loop_optimization, netcdf_64bit_3d, zu_s_inner, zw_w_inner, id_var_zusi_*,
    1010! id_var_zwwi_*, ts_value, u_nzb_p1_for_vfc, v_nzb_p1_for_vfc, pt_reference,
    11 ! use_pt_reference, precipitation_amount_interval
    12 ! +age_m in particle_type
    13 ! -data_output_ts, dots_n
    14 ! arrays dots_label and dots_unit now dimensioned with dots_max
     11! use_pt_reference, precipitation_amount_interval, revision
     12! +age_m in particle_type, moisture renamed humidity,
     13! -data_output_ts, dots_n, uvmean_outflow, uxrp, vynp,
     14! arrays dots_label and dots_unit now dimensioned with dots_max,
     15! setting of palm version moved to main program
    1516!
    1617! Former revisions:
     
    8182    REAL, DIMENSION(:), ALLOCATABLE ::                                         &
    8283          ddzu, dd2zu, dzu, ddzw, dzw, km_damp_x, km_damp_y, l_grid, pt_init,  &
    83           q_init, rdf, ug, uvmean_outflow, uvmean_outflow_l, u_init,           &
    84           u_nzb_p1_for_vfc, vg, v_init, v_nzb_p1_for_vfc, zu, zw
     84          q_init, rdf, ug, u_init, u_nzb_p1_for_vfc, vg, v_init,               &
     85          v_nzb_p1_for_vfc, zu, zw
    8586
    8687    REAL, DIMENSION(:,:), ALLOCATABLE ::                                       &
     
    9697
    9798    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
    98           d, diss, l_wall, tend
     99          d, diss, l_wall, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l, v_m_n,     &
     100          v_m_r, v_m_s, w_m_l, w_m_n, w_m_r, w_m_s
    99101
    100102    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
     
    111113          vpt, vpt_m, w, w_m, w_p
    112114
    113     REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  rif_wall, u_m_l, u_m_n, u_m_r,   &
    114           u_m_s, v_m_l, v_m_n, v_m_r, v_m_s, w_m_l, w_m_n, w_m_r, w_m_s
    115                                                    
     115    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  rif_wall
    116116
    117117    SAVE
     
    217217    CHARACTER (LEN=8)   ::  run_date, run_time
    218218    CHARACTER (LEN=9)   ::  simulated_time_chr
    219     CHARACTER (LEN=12)  ::  version = 'PALM   3.2'
     219    CHARACTER (LEN=12)  ::  version = ' ', revision = ' '
    220220    CHARACTER (LEN=16)  ::  loop_optimization = 'default', &
    221221                            momentum_advec = 'pw-scheme', &
     
    236236    CHARACTER (LEN=40)  ::  avs_data_file, topography = 'flat'
    237237    CHARACTER (LEN=64)  ::  host
    238     CHARACTER (LEN=80)  ::  log_message, run_description_header, run_identifier
    239     CHARACTER (LEN=100) ::  initializing_actions = ' '
     238    CHARACTER (LEN=80)  ::  log_message, run_identifier
     239    CHARACTER (LEN=100) ::  initializing_actions = ' ', run_description_header
    240240
    241241    CHARACTER (LEN=7),  DIMENSION(100) ::  do3d_comp_prec = ' '
     
    293293                first_call_advec_particles = .TRUE., &
    294294                force_print_header = .FALSE., galilei_transformation = .FALSE.,&
    295                 inflow_l = .FALSE., inflow_n = .FALSE., inflow_r = .FALSE., &
    296                 inflow_s = .FALSE., iso2d_output = .FALSE., &
    297                 mg_switch_to_pe0 = .FALSE., moisture = .FALSE., &
     295                humidity = .FALSE., inflow_l = .FALSE., inflow_n = .FALSE., &
     296                inflow_r = .FALSE., inflow_s = .FALSE., iso2d_output = .FALSE.,&
     297                mg_switch_to_pe0 = .FALSE., &
    298298                netcdf_output = .FALSE., netcdf_64bit = .FALSE., &
    299299                netcdf_64bit_3d = .TRUE., &
     
    528528    INTEGER ::  ngp_sums, nnx, nx = 0, nxa, nxl, nxr, nxra, nny, ny = 0, nya,  &
    529529                nyn, nyna, nys, nnz, nz = 0, nza, nzb, nzb_diff, nzt, nzta,    &
    530                 nzt_diff, uxrp = 0, vynp = 0
     530                nzt_diff
    531531
    532532    INTEGER, DIMENSION(:), ALLOCATABLE ::                                      &
     
    889889#if defined( __parallel )
    890890    INTEGER ::  comm1dx, comm1dy, comm2d, comm_palm, ierr, myidx, myidy,       &
    891                 ndim = 2, ngp_y, ngp_yz_p, pleft, pnorth, pright, psouth,      &
     891                ndim = 2, ngp_y, pleft, pnorth, pright, psouth,                &
    892892                sendrecvcount_xy, sendrecvcount_yz, sendrecvcount_zx,          &
    893893                sendrecvcount_zyd, sendrecvcount_yxd,                          &
    894                 type_x, type_x_int, type_xz_p, ibuf(12), pcoord(2), pdims(2),  &
     894                type_x, type_x_int, ibuf(12), pcoord(2), pdims(2),             &
    895895                status(MPI_STATUS_SIZE)
    896896
  • palm/trunk/SOURCE/palm.f90

    r70 r75  
    55! -----------------
    66! __vtk directives removed, write_particles is called only in case of particle
    7 ! advection switched on, open unit 9 for debug output
     7! advection switched on, open unit 9 for debug output,
     8! setting of palm version moved from modules to here
    89!
    910! Former revisions:
     
    5758    CHARACTER (LEN=1) ::  cdum
    5859    INTEGER           ::  i, run_description_header_i(80)
     60
     61    version = 'PALM 3.2'
    5962
    6063#if defined( __parallel )
  • palm/trunk/SOURCE/parin.f90

    r72 r75  
    55! -----------------
    66! +dt_max, netcdf_64bit_3d, precipitation_amount_interval in d3par,
    7 ! +loop_optimization, pt_reference in inipar, -data_output_ts
     7! +loop_optimization, pt_reference in inipar, -data_output_ts,
     8! moisture renamed humidity
    89!
    910! Former revisions:
     
    5859                       dz_stretch_factor, dz_stretch_level, e_min, &
    5960                       end_time_1d, fft_method, galilei_transformation, &
    60                        grid_matching, inflow_disturbance_begin, &
     61                       grid_matching, humidity, inflow_disturbance_begin, &
    6162                       inflow_disturbance_end, initializing_actions, &
    6263                       km_constant, km_damp_max, long_filter_factor, &
    63                        loop_optimization, mixing_length_1d, moisture, &
     64                       loop_optimization, mixing_length_1d, &
    6465                       momentum_advec, netcdf_precision, npex, npey, nsor_ini, &
    6566                       nx, ny, nz, omega, outflow_damping_width, &
     
    117118
    118119
    119     NAMELIST /envpar/  host, maximum_cpu_time_allowed, run_identifier, &
    120                        tasks_per_node, write_binary
     120    NAMELIST /envpar/  host, maximum_cpu_time_allowed, revision, &
     121                       run_identifier, tasks_per_node, write_binary
    121122
    122123
  • palm/trunk/SOURCE/poismg.f90

    r4 r75  
    88! Actual revisions:
    99! -----------------
    10 !
     10! 2nd+3rd argument removed from exchange horiz
    1111!
    1212! Former revisions:
     
    5959!
    6060!-- Some boundaries have to be added to divergence array
    61     CALL exchange_horiz( d, 0, 0 )
     61    CALL exchange_horiz( d )
    6262    d(nzb,:,:) = d(nzb+1,:,:)
    6363
     
    164164!
    165165!-- Horizontal boundary conditions
    166     CALL exchange_horiz( r, 0, 0 )
     166    CALL exchange_horiz( r )
    167167
    168168    IF ( bc_lr /= 'cyclic' )  THEN
     
    257257!
    258258!-- Horizontal boundary conditions
    259     CALL exchange_horiz( f_mg, 0, 0 )
     259    CALL exchange_horiz( f_mg )
    260260
    261261    IF ( bc_lr /= 'cyclic' )  THEN
     
    355355!
    356356!-- Horizontal boundary conditions
    357     CALL exchange_horiz( temp, 0, 0 )
     357    CALL exchange_horiz( temp )
    358358
    359359    IF ( bc_lr /= 'cyclic' )  THEN
     
    627627!
    628628!--       Horizontal boundary conditions
    629           CALL exchange_horiz( p_mg, 0, 0 )
     629          CALL exchange_horiz( p_mg )
    630630
    631631          IF ( bc_lr /= 'cyclic' )  THEN
  • palm/trunk/SOURCE/prandtl_fluxes.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! moisture renamed humidity
    77!
    88! Former revisions:
     
    9797!
    9898!-- Compute z_p/L (corresponds to the Richardson-flux number)
    99     IF ( .NOT. moisture ) THEN
     99    IF ( .NOT. humidity ) THEN
    100100       !$OMP PARALLEL DO PRIVATE( k, z_p )
    101101       DO  i = nxl-1, nxr+1
     
    274274!
    275275!-- If required compute q*
    276     IF ( moisture  .OR.  passive_scalar )  THEN
     276    IF ( humidity  .OR.  passive_scalar )  THEN
    277277       IF ( constant_waterflux )  THEN
    278278!
     
    332332    CALL exchange_horiz_2d( usws )
    333333    CALL exchange_horiz_2d( vsws )
    334     IF ( moisture  .OR.  passive_scalar )  CALL exchange_horiz_2d( qsws )
     334    IF ( humidity  .OR.  passive_scalar )  CALL exchange_horiz_2d( qsws )
    335335
    336336!
     
    347347!
    348348!-- Compute the vertical water/scalar flux
    349     IF ( .NOT. constant_heatflux .AND. ( moisture .OR. passive_scalar ) ) THEN
     349    IF ( .NOT. constant_heatflux .AND. ( humidity .OR. passive_scalar ) ) THEN
    350350       !$OMP PARALLEL DO
    351351       DO  i = nxl-1, nxr+1
  • palm/trunk/SOURCE/pres.f90

    r73 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Volume flow control for non-cyclic boundary conditions added (currently only
     7! for the north boundary!!), 2nd+3rd argument removed from exchange horiz
    78!
    89! Former revisions:
     
    5455       ALLOCATE( d(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
    5556    ENDIF
     57
     58!
     59!-- Conserve the volume flow at the outflow in case of non-cyclic lateral
     60!-- boundary conditions
     61    IF ( conserve_volume_flow  .AND.  bc_ns == 'radiation/dirichlet')  THEN
     62
     63       volume_flow(2)   = 0.0
     64       volume_flow_l(2) = 0.0
     65
     66       IF ( nyn == ny )  THEN
     67          j = ny+1
     68          DO  i = nxl, nxr
     69!
     70!--          Sum up the volume flow through the north boundary
     71             DO  k = nzb_2d(j,i) + 1, nzt
     72                volume_flow_l(2) = volume_flow_l(2) + v(k,j,i) * dzu(k)
     73             ENDDO
     74          ENDDO
     75       ENDIF
     76#if defined( __parallel )   
     77       CALL MPI_ALLREDUCE( volume_flow_l(2), volume_flow(2), 1, MPI_REAL, &
     78                           MPI_SUM, comm1dx, ierr )   
     79#else
     80       volume_flow = volume_flow_l 
     81#endif
     82       volume_flow_offset(2) = ( volume_flow_initial(2) - volume_flow(2) )    &
     83                               / volume_flow_area(2)                         
     84
     85       IF ( outflow_n )  THEN
     86          j = nyn+1
     87          DO  i = nxl, nxr
     88             DO  k = nzb_v_inner(j,i) + 1, nzt
     89                v(k,j,i) = v(k,j,i) + volume_flow_offset(2)
     90             ENDDO
     91          ENDDO
     92       ENDIF
     93
     94       CALL exchange_horiz( v )
     95
     96    ENDIF
     97
    5698
    5799!
     
    322364!
    323365!--    Exchange boundaries for p
    324        CALL exchange_horiz( tend, 0, 0 )
     366       CALL exchange_horiz( tend )
    325367     
    326368    ELSEIF ( psolver == 'sor' )  THEN
     
    365407!-- Correction of the provisional velocities with the current perturbation
    366408!-- pressure just computed
    367     IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  uvmean_outflow_l = 0.0
    368     IF ( conserve_volume_flow )  THEN
     409    IF ( conserve_volume_flow  .AND. &
     410         ( bc_lr == 'cyclic'  .OR.  bc_ns == 'cyclic' ) )  THEN
    369411       volume_flow_l(1) = 0.0
    370412       volume_flow_l(2) = 0.0
     
    393435
    394436!
    395 !--       Sum up the horizontal velocity along the outflow plane (in case
    396 !--       of non-cyclic boundary conditions). The respective mean velocity
    397 !--       is calculated from this in routine boundary_conds.
    398 !          IF ( outflow_l  .AND.  i == nxl )  THEN
    399 !             !$OMP CRITICAL
    400 !             DO  k = nzb, nzt+1
    401 !                uvmean_outflow_l(k) = uvmean_outflow_l(k) + v(k,j,nxl)
    402 !             ENDDO
    403 !             !$OMP END CRITICAL
    404 !          ELSEIF ( outflow_r  .AND.  i == nxr )  THEN
    405 !             !$OMP CRITICAL
    406 !             DO  k = nzb, nzt+1
    407 !                uvmean_outflow_l(k) = uvmean_outflow_l(k) + v(k,j,nxr)
    408 !             ENDDO
    409 !             !$OMP END CRITICAL
    410 !          ELSEIF ( outflow_s  .AND.  j == nys )  THEN
    411 !             !$OMP CRITICAL
    412 !             DO  k = nzb, nzt+1
    413 !                uvmean_outflow_l(k) = uvmean_outflow_l(k) + u(k,nys,i)
    414 !             ENDDO
    415 !             !$OMP END CRITICAL
    416 !          ELSEIF ( outflow_n  .AND.  j == nyn )  THEN
    417 !             !$OMP CRITICAL
    418 !             DO  k = nzb, nzt+1
    419 !                uvmean_outflow_l(k) = uvmean_outflow_l(k) + u(k,nyn,i)
    420 !             ENDDO
    421 !             !$OMP END CRITICAL
    422 !          ENDIF
    423 
    424 !
    425437!--       Sum up the volume flow through the right and north boundary
    426           IF ( conserve_volume_flow  .AND.  i == nx )  THEN
     438          IF ( conserve_volume_flow  .AND.  bc_lr == 'cyclic'  .AND. &
     439               i == nx )  THEN
    427440             !$OMP CRITICAL
    428441             DO  k = nzb_2d(j,i) + 1, nzt
     
    431444             !$OMP END CRITICAL
    432445          ENDIF
    433           IF ( conserve_volume_flow  .AND.  j == ny )  THEN
     446          IF ( conserve_volume_flow  .AND.  bc_ns == 'cyclic'  .AND. &
     447               j == ny )  THEN
    434448             !$OMP CRITICAL
    435449             DO  k = nzb_2d(j,i) + 1, nzt
     
    445459!
    446460!-- Conserve the volume flow
    447     IF ( conserve_volume_flow )  THEN
     461    IF ( conserve_volume_flow  .AND. &
     462         ( bc_lr == 'cyclic'  .OR.  bc_ns == 'cyclic' ) )  THEN
    448463
    449464#if defined( __parallel )   
     
    461476       DO  i = nxl, nxr
    462477          DO  j = nys, nyn
    463              DO  k = nzb_u_inner(j,i) + 1, nzt
    464                 u(k,j,i) = u(k,j,i) + volume_flow_offset(1)
    465              ENDDO
    466              DO  k = nzb_v_inner(j,i) + 1, nzt
    467                 v(k,j,i) = v(k,j,i) + volume_flow_offset(2)
    468              ENDDO
     478             IF ( bc_lr == 'cyclic' )  THEN
     479                DO  k = nzb_u_inner(j,i) + 1, nzt
     480                   u(k,j,i) = u(k,j,i) + volume_flow_offset(1)
     481                ENDDO
     482             ENDIF
     483             IF ( bc_ns == 'cyclic' )  THEN
     484                DO  k = nzb_v_inner(j,i) + 1, nzt
     485                   v(k,j,i) = v(k,j,i) + volume_flow_offset(2)
     486                ENDDO
     487             ENDIF
    469488          ENDDO
    470489       ENDDO
     
    475494!
    476495!-- Exchange of boundaries for the velocities
    477     CALL exchange_horiz( u, uxrp,    0 )
    478     CALL exchange_horiz( v,    0, vynp )
    479     CALL exchange_horiz( w,    0,    0 )
     496    CALL exchange_horiz( u )
     497    CALL exchange_horiz( v )
     498    CALL exchange_horiz( w )
    480499
    481500!
  • palm/trunk/SOURCE/production_e.f90

    r73 r75  
    55! -----------------
    66! Wall functions now include diabatic conditions, call of routine wall_fluxes_e,
    7 ! reference temperature pt_reference can be used in buoyancy term
     7! reference temperature pt_reference can be used in buoyancy term,
     8! moisture renamed humidity
    89!
    910! Former revisions:
     
    358359!
    359360!--       Calculate TKE production by buoyancy
    360           IF ( .NOT. moisture )  THEN
     361          IF ( .NOT. humidity )  THEN
    361362
    362363             IF ( use_pt_reference )  THEN
     
    756757!
    757758!--    Calculate TKE production by buoyancy
    758        IF ( .NOT. moisture )  THEN
     759       IF ( .NOT. humidity )  THEN
    759760
    760761          IF ( use_pt_reference )  THEN
  • palm/trunk/SOURCE/prognostic_equations.f90

    r73 r75  
    55! -----------------
    66! checking for negative q and limiting for positive values,
    7 ! z0 removed from arguments in calls of diffusion_u/v/w,
    8 ! subroutine names changed to .._noopt, .._cache, and .._vector
     7! z0 removed from arguments in calls of diffusion_u/v/w, uxrp, vynp eliminated,
     8! subroutine names changed to .._noopt, .._cache, and .._vector,
     9! moisture renamed humidity
    910!
    1011! Former revisions:
     
    102103!-- global communication
    103104    CALL calc_mean_pt_profile( pt, 4 )
    104     IF ( moisture )  CALL calc_mean_pt_profile( vpt, 44 )
     105    IF ( humidity )  CALL calc_mean_pt_profile( vpt, 44 )
    105106
    106107!
     
    117118!
    118119!-- u-tendency terms with no communication
    119     DO  i = nxl, nxr+uxrp
     120    DO  i = nxl, nxr
    120121       DO  j = nys, nyn
    121122!
     
    186187!-- v-tendency terms with no communication
    187188    DO  i = nxl, nxr
    188        DO  j = nys, nyn+vynp
     189       DO  j = nys, nyn
    189190!
    190191!--       Tendency terms
     
    273274          ENDIF
    274275          CALL coriolis( i, j, 3 )
    275           IF ( .NOT. moisture )  THEN
     276          IF ( .NOT. humidity )  THEN
    276277             CALL buoyancy( i, j, pt, 3, 4 )
    277278          ELSE
     
    410411!
    411412!-- If required, compute prognostic equation for total water content / scalar
    412     IF ( moisture  .OR.  passive_scalar )  THEN
     413    IF ( humidity  .OR.  passive_scalar )  THEN
    413414
    414415       CALL cpu_log( log_point(29), 'q/s-equation', 'start' )
     
    550551             IF ( scalar_advec == 'bc-scheme'  .AND.  &
    551552                  .NOT. use_upstream_for_tke )  THEN
    552                 IF ( .NOT. moisture )  THEN
     553                IF ( .NOT. humidity )  THEN
    553554                   CALL diffusion_e( i, j, ddzu, dd2zu, ddzw, diss, e, km, &
    554555                                     l_grid, pt, rif, tend, zu )
     
    575576                IF ( tsc(2) == 2.0  .AND.  timestep_scheme(1:8) == 'leapfrog' )&
    576577                THEN
    577                    IF ( .NOT. moisture )  THEN
     578                   IF ( .NOT. humidity )  THEN
    578579                      CALL diffusion_e( i, j, ddzu, dd2zu, ddzw, diss, e_m, &
    579580                                        km_m, l_grid, pt_m, rif_m, tend, zu )
     
    583584                   ENDIF
    584585                ELSE
    585                    IF ( .NOT. moisture )  THEN
     586                   IF ( .NOT. humidity )  THEN
    586587                      CALL diffusion_e( i, j, ddzu, dd2zu, ddzw, diss, e, km, &
    587588                                        l_grid, pt, rif, tend, zu )
     
    661662!-- global communication
    662663    CALL calc_mean_pt_profile( pt, 4 )
    663     IF ( moisture )  CALL calc_mean_pt_profile( vpt, 44 )
     664    IF ( humidity )  CALL calc_mean_pt_profile( vpt, 44 )
    664665    IF ( .NOT. constant_diffusion )  CALL production_e_init
    665666
     
    669670!$OMP PARALLEL private (i,j,k)
    670671!$OMP DO
    671     DO  i = nxl, nxr+uxrp       ! Additional levels for non cyclic boundary
    672        DO  j = nys, nyn+vynp    ! conditions are included
     672    DO  i = nxl, nxr
     673       DO  j = nys, nyn
    673674!
    674675!--       Tendency terms for u-velocity component
     
    789790             ENDIF
    790791             CALL coriolis( i, j, 3 )
    791              IF ( .NOT. moisture )  THEN
     792             IF ( .NOT. humidity )  THEN
    792793                CALL buoyancy( i, j, pt, 3, 4 )
    793794             ELSE
     
    881882!--          If required, compute prognostic equation for total water content /
    882883!--          scalar
    883              IF ( moisture  .OR.  passive_scalar )  THEN
     884             IF ( humidity  .OR.  passive_scalar )  THEN
    884885
    885886!
     
    954955                IF ( tsc(2) == 2.0  .AND.  timestep_scheme(1:8) == 'leapfrog' )&
    955956                THEN
    956                    IF ( .NOT. moisture )  THEN
     957                   IF ( .NOT. humidity )  THEN
    957958                      CALL diffusion_e( i, j, ddzu, dd2zu, ddzw, diss, e_m, &
    958959                                        km_m, l_grid, pt_m, rif_m, tend, zu )
     
    962963                   ENDIF
    963964                ELSE
    964                    IF ( .NOT. moisture )  THEN
     965                   IF ( .NOT. humidity )  THEN
    965966                      CALL diffusion_e( i, j, ddzu, dd2zu, ddzw, diss, e, km, &
    966967                                        l_grid, pt, rif, tend, zu )
     
    10321033!-- global communication
    10331034    CALL calc_mean_pt_profile( pt, 4 )
    1034     IF ( moisture )  CALL calc_mean_pt_profile( vpt, 44 )
     1035    IF ( humidity )  CALL calc_mean_pt_profile( vpt, 44 )
    10351036
    10361037!
     
    10681069!
    10691070!-- Prognostic equation for u-velocity component
    1070     DO  i = nxl, nxr+uxrp
     1071    DO  i = nxl, nxr
    10711072       DO  j = nys, nyn
    10721073          DO  k = nzb_u_inner(j,i)+1, nzt
     
    10851086    IF ( timestep_scheme(1:5) == 'runge' )  THEN
    10861087       IF ( intermediate_timestep_count == 1 )  THEN
    1087           DO  i = nxl, nxr+uxrp
     1088          DO  i = nxl, nxr
    10881089             DO  j = nys, nyn
    10891090                DO  k = nzb_u_inner(j,i)+1, nzt
     
    10941095       ELSEIF ( intermediate_timestep_count < &
    10951096                intermediate_timestep_count_max )  THEN
    1096           DO  i = nxl, nxr+uxrp
     1097          DO  i = nxl, nxr
    10971098             DO  j = nys, nyn
    10981099                DO  k = nzb_u_inner(j,i)+1, nzt
     
    11401141!-- Prognostic equation for v-velocity component
    11411142    DO  i = nxl, nxr
    1142        DO  j = nys, nyn+vynp
     1143       DO  j = nys, nyn
    11431144          DO  k = nzb_v_inner(j,i)+1, nzt
    11441145             v_p(k,j,i) = ( 1.0-tsc(1) ) * v_m(k,j,i) + tsc(1) * v(k,j,i) +    &
     
    11571158       IF ( intermediate_timestep_count == 1 )  THEN
    11581159          DO  i = nxl, nxr
    1159              DO  j = nys, nyn+vynp
     1160             DO  j = nys, nyn
    11601161                DO  k = nzb_v_inner(j,i)+1, nzt
    11611162                   tv_m(k,j,i) = tend(k,j,i)
     
    11661167                intermediate_timestep_count_max )  THEN
    11671168          DO  i = nxl, nxr
    1168              DO  j = nys, nyn+vynp
     1169             DO  j = nys, nyn
    11691170                DO  k = nzb_v_inner(j,i)+1, nzt
    11701171                   tv_m(k,j,i) = -9.5625 * tend(k,j,i) + 5.3125 * tv_m(k,j,i)
     
    12061207    ENDIF
    12071208    CALL coriolis( 3 )
    1208     IF ( .NOT. moisture )  THEN
     1209    IF ( .NOT. humidity )  THEN
    12091210       CALL buoyancy( pt, 3, 4 )
    12101211    ELSE
     
    13551356!
    13561357!-- If required, compute prognostic equation for total water content / scalar
    1357     IF ( moisture  .OR.  passive_scalar )  THEN
     1358    IF ( humidity  .OR.  passive_scalar )  THEN
    13581359
    13591360       CALL cpu_log( log_point(29), 'q/s-equation', 'start' )
     
    14931494       IF ( scalar_advec == 'bc-scheme'  .AND.  .NOT. use_upstream_for_tke )  &
    14941495       THEN
    1495           IF ( .NOT. moisture )  THEN
     1496          IF ( .NOT. humidity )  THEN
    14961497             CALL diffusion_e( ddzu, dd2zu, ddzw, diss, e, km, l_grid, pt, &
    14971498                               rif, tend, zu )
     
    15161517          ENDIF
    15171518          IF ( tsc(2) == 2.0  .AND.  timestep_scheme(1:8) == 'leapfrog' )  THEN
    1518              IF ( .NOT. moisture )  THEN
     1519             IF ( .NOT. humidity )  THEN
    15191520                CALL diffusion_e( ddzu, dd2zu, ddzw, diss, e_m, km_m, l_grid, &
    15201521                                  pt_m, rif_m, tend, zu )
     
    15241525             ENDIF
    15251526          ELSE
    1526              IF ( .NOT. moisture )  THEN
     1527             IF ( .NOT. humidity )  THEN
    15271528                CALL diffusion_e( ddzu, dd2zu, ddzw, diss, e, km, l_grid, pt, &
    15281529                                  rif, tend, zu )
  • palm/trunk/SOURCE/read_var_list.f90

    r63 r75  
    44! Actual revisions:
    55! -----------------
    6 ! +loop_optimization, pt_reference
     6! +loop_optimization, pt_reference, moisture renamed humidity
    77!
    88! Former revisions:
     
    212212          CASE ( 'mixing_length_1d' )
    213213             READ ( 13 )  mixing_length_1d
    214           CASE ( 'moisture' )
    215              READ ( 13 )  moisture
     214          CASE ( 'humidity' )
     215             READ ( 13 )  humidity
    216216          CASE ( 'momentum_advec' )
    217217             READ ( 13 )  momentum_advec
  • palm/trunk/SOURCE/sor.f90

    r4 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    9898!
    9999!--    Exchange of boundary values for p.
    100        CALL exchange_horiz( p, 0, 0 )
     100       CALL exchange_horiz( p )
    101101
    102102!
     
    143143!
    144144!--    Exchange of boundary values for p.
    145        CALL exchange_horiz( p, 0, 0 )
     145       CALL exchange_horiz( p )
    146146
    147147!
  • palm/trunk/SOURCE/swap_timelevel.f90

    r39 r75  
    44! Actual revisions:
    55! -----------------
    6 !
     6! moisture renamed humidity
    77!
    88! Former revisions:
     
    5656                e_m => e_1;  e => e_2;  e_p => e_3
    5757             ENDIF
    58              IF ( moisture  .OR.  passive_scalar )  THEN
     58             IF ( humidity  .OR.  passive_scalar )  THEN
    5959                q_m => q_1;  q => q_2;  q_p => q_3
    6060             ENDIF
     
    6969                e_m => e_2;  e => e_3;  e_p => e_1
    7070             ENDIF
    71              IF ( moisture  .OR.  passive_scalar )  THEN
     71             IF ( humidity  .OR.  passive_scalar )  THEN
    7272                q_m => q_2;  q => q_3;  q_p => q_1
    7373             ENDIF
     
    8282                e_m => e_3;  e => e_1;  e_p => e_2
    8383             ENDIF
    84              IF ( moisture  .OR.  passive_scalar )  THEN
     84             IF ( humidity  .OR.  passive_scalar )  THEN
    8585                q_m => q_3;  q => q_1;  q_p => q_2
    8686             ENDIF
     
    105105                e => e_1;  e_p => e_2
    106106             ENDIF
    107              IF ( moisture  .OR.  passive_scalar )  THEN
     107             IF ( humidity  .OR.  passive_scalar )  THEN
    108108                q => q_1;  q_p => q_2
    109109             ENDIF
     
    119119                   vsws_m => vsws_1;  vsws => vsws_2
    120120                   shf_m  => shf_1;   shf  => shf_2
    121                    IF ( moisture  .OR.  passive_scalar )  THEN
     121                   IF ( humidity  .OR.  passive_scalar )  THEN
    122122                      qsws_m => qsws_1;  qsws => qsws_2
    123123                   ENDIF
     
    128128                IF ( use_top_fluxes )  THEN
    129129                   tswst_m => tswst_1;  tswst => tswst_2
    130                    IF ( moisture  .OR.  passive_scalar )  THEN
     130                   IF ( humidity  .OR.  passive_scalar )  THEN
    131131                      qswst_m => qswst_1;  qswst => qswst_2
    132132                   ENDIF
     
    134134             ENDIF
    135135
    136              IF ( moisture )  THEN
     136             IF ( humidity )  THEN
    137137                vpt_m => vpt_1;  vpt => vpt_2
    138138             ENDIF
     
    151151                e => e_2;  e_p => e_1
    152152             ENDIF
    153              IF ( moisture  .OR.  passive_scalar )  THEN
     153             IF ( humidity  .OR.  passive_scalar )  THEN
    154154                q => q_2;  q_p => q_1
    155155             ENDIF
     
    164164                   vsws_m => vsws_2;  vsws => vsws_1
    165165                   shf_m  => shf_2;   shf  => shf_1
    166                    IF ( moisture  .OR.  passive_scalar )  THEN
     166                   IF ( humidity  .OR.  passive_scalar )  THEN
    167167                      qsws_m => qsws_2;  qsws => qsws_1
    168168                   ENDIF
     
    173173                IF ( use_top_fluxes )  THEN
    174174                   tswst_m  => tswst_2;  tswst => tswst_1
    175                    IF ( moisture  .OR.  passive_scalar )  THEN
     175                   IF ( humidity  .OR.  passive_scalar )  THEN
    176176                      qswst_m => qswst_2;  qswst => qswst_1
    177177                   ENDIF
     
    179179             ENDIF
    180180
    181              IF ( moisture )  THEN
     181             IF ( humidity )  THEN
    182182                vpt_m => vpt_2;  vpt => vpt_1
    183183             ENDIF
  • palm/trunk/SOURCE/time_integration.f90

    r73 r75  
    77! and counters,
    88! calls of prognostic_equations_.. changed to .._noopt, .._cache, and
    9 ! .._vector, these calls are now controlled by switch loop_optimization
     9! .._vector, these calls are now controlled by switch loop_optimization,
     10! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz,
     11! moisture renamed humidity
    1012!
    1113! Former revisions:
     
    136138!--       Exchange of ghost points (lateral boundary conditions)
    137139          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
    138           CALL exchange_horiz( u_p, uxrp,    0 )
    139           CALL exchange_horiz( v_p,    0, vynp )
    140           CALL exchange_horiz( w_p,    0,    0 )
    141           CALL exchange_horiz( pt_p,   0,    0 )
    142           IF ( .NOT. constant_diffusion       )  CALL exchange_horiz( e_p, 0, 0)
    143           IF ( moisture  .OR.  passive_scalar )  CALL exchange_horiz( q_p, 0, 0)
     140          CALL exchange_horiz( u_p )
     141          CALL exchange_horiz( v_p )
     142          CALL exchange_horiz( w_p )
     143          CALL exchange_horiz( pt_p )
     144          IF ( .NOT. constant_diffusion       )  CALL exchange_horiz( e_p )
     145          IF ( humidity  .OR.  passive_scalar )  CALL exchange_horiz( q_p )
    144146          IF ( cloud_droplets )  THEN
    145              CALL exchange_horiz( ql,    0, 0 )
    146              CALL exchange_horiz( ql_c,  0, 0 )
    147              CALL exchange_horiz( ql_v,  0, 0 )
    148              CALL exchange_horiz( ql_vp, 0, 0 )
     147             CALL exchange_horiz( ql )
     148             CALL exchange_horiz( ql_c )
     149             CALL exchange_horiz( ql_v )
     150             CALL exchange_horiz( ql_vp )
    149151          ENDIF
    150152
     
    182184             IF ( time_disturb >= dt_disturb )  THEN
    183185                IF ( hom(nzb+5,1,var_hom,0) < disturbance_energy_limit )  THEN
    184                    CALL disturb_field( nzb_u_inner, tend, u, uxrp, 0    )
    185                    CALL disturb_field( nzb_v_inner, tend, v ,   0, vynp )
     186                   CALL disturb_field( nzb_u_inner, tend, u )
     187                   CALL disturb_field( nzb_v_inner, tend, v )
    186188                ELSEIF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    187189!
     
    189191!--                near the inflow throughout the whole simulation
    190192                   dist_range = 1
    191                    CALL disturb_field( nzb_u_inner, tend, u, uxrp, 0    )
    192                    CALL disturb_field( nzb_v_inner, tend, v ,   0, vynp )
     193                   CALL disturb_field( nzb_u_inner, tend, u )
     194                   CALL disturb_field( nzb_v_inner, tend, v )
    193195                   dist_range = 0
    194196                ENDIF
     
    208210!--       In case of a non-cyclic lateral wall, set the boundary conditions for
    209211!--       the velocities at the outflow
    210           IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    211              CALL boundary_conds( 'outflow_uvw' )
    212           ENDIF
     212!          IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
     213!             CALL boundary_conds( 'outflow_uvw' )
     214!          ENDIF
    213215
    214216!
    215217!--       If required, compute virtuell potential temperature
    216           IF ( moisture ) CALL compute_vpt
     218          IF ( humidity ) CALL compute_vpt
    217219
    218220!
     
    235237!--          Compute the diffusion coefficients
    236238             CALL cpu_log( log_point(17), 'diffusivities', 'start' )
    237              IF ( .NOT. moisture ) THEN
     239             IF ( .NOT. humidity ) THEN
    238240                CALL diffusivities( pt )
    239241             ELSE
  • palm/trunk/SOURCE/wall_fluxes.f90

    r60 r75  
    3737! Call for all grid points
    3838!------------------------------------------------------------------------------!
    39     SUBROUTINE wall_fluxes( wall_flux, a, b, c1, c2, ixp, jyp, nzb_uvw_inner, &
     39    SUBROUTINE wall_fluxes( wall_flux, a, b, c1, c2, nzb_uvw_inner, &
    4040                            nzb_uvw_outer, wall )
    4141
     
    4848       IMPLICIT NONE
    4949
    50        INTEGER ::  i, ixp, j, jyp, k, wall_index
     50       INTEGER ::  i, j, k, wall_index
    5151
    5252       INTEGER, DIMENSION(nys-1:nyn+1,nxl-1:nxr+1) ::  nzb_uvw_inner, &
     
    5555       REAL ::  pts, pt_i, rifs, u_i, v_i, us_wall, vel_total, ws, wspts
    5656
    57        REAL, DIMENSION(nys-1:nyn+1,nxl-1:nxr+1)           ::  wall
    58        REAL, DIMENSION(nzb:nzt+1,nys:nyn+jyp,nxl:nxr+ixp) ::  wall_flux
     57       REAL, DIMENSION(nys-1:nyn+1,nxl-1:nxr+1)   ::  wall
     58       REAL, DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr) ::  wall_flux
    5959
    6060
     
    6363       wall_index = NINT( a+ 2*b + 3*c1 + 4*c2 )
    6464
    65        DO  i = nxl, nxr+ixp
    66           DO  j = nys, nyn+jyp
     65       DO  i = nxl, nxr
     66          DO  j = nys, nyn
    6767
    6868             IF ( wall(j,i) /= 0.0 )  THEN
  • palm/trunk/SOURCE/write_3d_binary.f90

    r73 r75  
    55! -----------------
    66! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
    7 ! z0_av
     7! z0_av, moisture renamed humidity
    88!
    99! Former revisions:
     
    107107    ENDIF
    108108    WRITE ( 14 )  'pt_m                ';  WRITE ( 14 )  pt_m
    109     IF ( moisture  .OR. passive_scalar )  THEN
     109    IF ( humidity  .OR. passive_scalar )  THEN
    110110       WRITE ( 14 )  'q                   ';  WRITE ( 14 )  q
    111111       IF ( ALLOCATED( q_av ) )  THEN
     
    209209       WRITE ( 14 )  'v_m_s               ';  WRITE ( 14 )  v_m_s
    210210    ENDIF
    211     IF ( moisture )  THEN
     211    IF ( humidity )  THEN
    212212       WRITE ( 14 )  'vpt                 ';  WRITE ( 14 )  vpt
    213213       IF ( ALLOCATED( vpt_av ) )  THEN
  • palm/trunk/SOURCE/write_var_list.f90

    r63 r75  
    44! Actual revisions:
    55! -----------------
    6 ! +loop_optimization, pt_refrence
     6! +loop_optimization, pt_refrence, moisture renamed humidity
    77!
    88! Former revisions:
     
    178178    WRITE ( 14 )  'mixing_length_1d              '
    179179    WRITE ( 14 )  mixing_length_1d
    180     WRITE ( 14 )  'moisture                      '
    181     WRITE ( 14 )  moisture
     180    WRITE ( 14 )  'humidity                      '
     181    WRITE ( 14 )  humidity
    182182    WRITE ( 14 )  'momentum_advec                '
    183183    WRITE ( 14 )  momentum_advec
Note: See TracChangeset for help on using the changeset viewer.