Ignore:
Timestamp:
Jul 12, 2016 4:34:24 PM (8 years ago)
Author:
suehring
Message:

Separate balance equations for humidity and passive_scalar

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/surface_layer_fluxes_mod.f90

    r1930 r1960  
    1919! Current revisions:
    2020! ------------------
    21 !  
     21! Treat humidity and passive scalar separately
    2222!
    2323! Former revisions:
     
    141141    USE arrays_3d,                                                             &
    142142        ONLY:  e, kh, nr, nrs, nrsws, ol, pt, q, ql, qr, qrs, qrsws, qs, qsws, &
    143                shf, ts, u, us, usws, v, vpt, vsws, zu, zw, z0, z0h, z0q
     143               s, shf, ss, ssws, ts, u, us, usws, v, vpt, vsws, zu, zw, z0,    &
     144               z0h, z0q
    144145
    145146    USE cloud_parameters,                                                      &
     
    152153
    153154    USE control_parameters,                                                    &
    154         ONLY:  cloud_physics, constant_heatflux, constant_waterflux,           &
    155                coupling_mode, g, humidity, ibc_e_b, ibc_pt_b,                  &
    156                initializing_actions, kappa, intermediate_timestep_count,       &
     155        ONLY:  cloud_physics, constant_heatflux, constant_scalarflux,          &
     156               constant_waterflux, coupling_mode, g, humidity, ibc_e_b,        &
     157               ibc_pt_b, initializing_actions, kappa,                          &
     158               intermediate_timestep_count,                                    &
    157159               intermediate_timestep_count_max, large_scale_forcing, lsf_surf, &
    158160               message_string, microphysics_seifert, most_method, neutral,     &
     
    859861!
    860862!--    If required compute q*
    861        IF ( humidity  .OR.  passive_scalar )  THEN
     863       IF ( humidity )  THEN
    862864          IF ( constant_waterflux )  THEN
    863865!
     
    922924          ENDIF
    923925       ENDIF
     926       
     927!
     928!--    If required compute s*
     929       IF ( passive_scalar )  THEN
     930          IF ( constant_scalarflux )  THEN
     931!
     932!--          For a given water flux in the surface layer
     933             !$OMP PARALLEL DO
     934             !$acc kernels loop private( j )
     935             DO  i = nxlg, nxrg
     936                DO  j = nysg, nyng
     937                   ss(j,i) = -ssws(j,i) / ( us(j,i) + 1E-30_wp )
     938                ENDDO
     939             ENDDO
     940          ENDIF
     941       ENDIF
    924942
    925943
     
    10431061
    10441062!
    1045 !-- Compute the vertical water/scalar flux
    1046        IF (  .NOT.  constant_waterflux  .AND.  ( humidity  .OR.                &
    1047              passive_scalar )  .AND.  ( simulated_time <= skip_time_do_lsm     &
     1063!--    Compute the vertical water flux
     1064       IF (  .NOT.  constant_waterflux  .AND.  humidity  .AND.                 &
     1065             ( simulated_time <= skip_time_do_lsm                              &
    10481066            .OR.  .NOT.  land_surface ) )  THEN
    10491067          !$OMP PARALLEL DO
     
    10571075
    10581076       ENDIF
     1077       
     1078!
     1079!--    Compute the vertical scalar flux
     1080       IF (  .NOT.  constant_scalarflux  .AND.  passive_scalar  .AND.          &
     1081             ( simulated_time <= skip_time_do_lsm                              &
     1082            .OR.  .NOT.  land_surface ) )  THEN
     1083          !$OMP PARALLEL DO
     1084          !$acc kernels loop independent present( qs, qsws, us )
     1085          DO  i = nxlg, nxrg
     1086             !$acc loop independent
     1087             DO  j = nysg, nyng
     1088                ssws(j,i) = -ss(j,i) * us(j,i)
     1089             ENDDO
     1090          ENDDO
     1091
     1092       ENDIF       
    10591093
    10601094!
Note: See TracChangeset for help on using the changeset viewer.