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

Separate balance equations for humidity and passive_scalar

File:
1 edited

Legend:

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

    r1818 r1960  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Remove passive_scalar from IF-statements, as 1D-scalar profile is effectively
     22! not used.
     23! Formatting adjustment
    2224!
    2325! Former revisions:
     
    108110    USE control_parameters,                                                    &
    109111        ONLY:  constant_diffusion, constant_flux_layer, f, humidity, kappa,    &
    110                km_constant, mixing_length_1d, passive_scalar, prandtl_number,  &
     112               km_constant, mixing_length_1d, prandtl_number,                  &
    111113               roughness_length, simulated_time_chr, z0h_factor
    112114
     
    194196    z01d  = roughness_length
    195197    z0h1d = z0h_factor * z01d
    196     IF ( humidity .OR. passive_scalar )  qs1d = 0.0_wp
     198    IF ( humidity )  qs1d = 0.0_wp
    197199
    198200!
     
    232234               humidity, intermediate_timestep_count,                          &
    233235               intermediate_timestep_count_max, f, g, ibc_e_b, kappa,          & 
    234                mixing_length_1d, passive_scalar,                               &
     236               mixing_length_1d,                                               &
    235237               simulated_time_chr, timestep_scheme, tsc, zeta_max, zeta_min
    236238               
     
    619621                e1d(nzb) = e1d(nzb+1)
    620622
    621                 IF ( humidity .OR. passive_scalar ) THEN
     623                IF ( humidity ) THEN
    622624!
    623625!--                Compute q*
    624626                   IF ( rif1d(1) >= 0.0_wp )  THEN
    625627!
    626 !--                Stable stratification
    627                    qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /            &
     628!--                   Stable stratification
     629                      qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /         &
    628630                          ( LOG( zu(nzb+1) / z0h1d ) + 5.0_wp * rif1d(nzb+1) * &
    629631                                          ( zu(nzb+1) - z0h1d ) / zu(nzb+1)    &
    630632                          )
    631                 ELSE
    632 !
    633 !--                Unstable stratification
    634                    a = SQRT( 1.0_wp - 16.0_wp * rif1d(nzb+1) )
    635                    b = SQRT( 1.0_wp - 16.0_wp * rif1d(nzb+1) /                 &
    636                                       zu(nzb+1) * z0h1d )
    637 !
    638 !--                In the borderline case the formula for stable stratification
    639 !--                must be applied, because otherwise a zero division would
    640 !--                occur in the argument of the logarithm.
    641                    IF ( a == 1.0_wp  .OR.  b == 1.0_wp )  THEN
    642                       qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /         &
    643                              ( LOG( zu(nzb+1) / z0h1d ) +                      &
    644                                5.0_wp * rif1d(nzb+1) *                         &
    645                                ( zu(nzb+1) - z0h1d ) / zu(nzb+1)               &
    646                              )
    647633                   ELSE
    648                       qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /         &
    649                              LOG( (a-1.0_wp) / (a+1.0_wp) *                    &
    650                                   (b+1.0_wp) / (b-1.0_wp) )
    651                    ENDIF
    652                 ENDIF               
     634!
     635!--                   Unstable stratification
     636                      a = SQRT( 1.0_wp - 16.0_wp * rif1d(nzb+1) )
     637                      b = SQRT( 1.0_wp - 16.0_wp * rif1d(nzb+1) /              &
     638                                         zu(nzb+1) * z0h1d )
     639!
     640!--                   In the borderline case the formula for stable stratification
     641!--                   must be applied, because otherwise a zero division would
     642!--                   occur in the argument of the logarithm.
     643                      IF ( a == 1.0_wp  .OR.  b == 1.0_wp )  THEN
     644                         qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /      &
     645                                ( LOG( zu(nzb+1) / z0h1d ) +                   &
     646                                  5.0_wp * rif1d(nzb+1) *                      &
     647                                  ( zu(nzb+1) - z0h1d ) / zu(nzb+1)            &
     648                                )
     649                      ELSE
     650                         qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /      &
     651                                LOG( (a-1.0_wp) / (a+1.0_wp) *                 &
     652                                     (b+1.0_wp) / (b-1.0_wp) )
     653                      ENDIF
     654                   ENDIF               
    653655                ELSE
    654656                   qs1d = 0.0_wp
Note: See TracChangeset for help on using the changeset viewer.