Ignore:
Timestamp:
Oct 26, 2015 4:17:44 PM (8 years ago)
Author:
maronga
Message:

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

File:
1 edited

Legend:

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

    r1683 r1691  
    1414! PALM. If not, see <http://www.gnu.org/licenses/>.
    1515!
    16 ! Copyright 1997-2014 Leibniz Universitaet Hannover
     16! Copyright 1997-2015 Leibniz Universitaet Hannover
    1717!--------------------------------------------------------------------------------!
    1818!
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Renamed prandtl_layer to constant_flux_layer. rif is replaced by ol and zeta.
    2222!
    2323! Former revisions:
     
    7272!> of the wind profile is being computed.
    7373!> All subroutines required can be found within this file.
     74!>
     75!> @todo harmonize code with new surface_layer_fluxes module
    7476!------------------------------------------------------------------------------!
    7577 SUBROUTINE init_1d_model
     
    9092   
    9193    USE control_parameters,                                                    &
    92         ONLY:  constant_diffusion, f, humidity, kappa, km_constant,            &
    93                mixing_length_1d, passive_scalar, prandtl_layer,                &
    94                prandtl_number, roughness_length, simulated_time_chr,           &
    95                z0h_factor
     94        ONLY:  constant_diffusion, constant_flux_layer, f, humidity, kappa,    &
     95               km_constant, mixing_length_1d, passive_scalar, prandtl_number,  &
     96               roughness_length, simulated_time_chr, z0h_factor
    9697
    9798    IMPLICIT NONE
     
    166167!
    167168!-- For u*, theta* and the momentum fluxes plausible values are set
    168     IF ( prandtl_layer )  THEN
     169    IF ( constant_flux_layer )  THEN
    169170       us1d = 0.1_wp   ! without initial friction the flow would not change
    170171    ELSE
     
    213214       
    214215    USE control_parameters,                                                    &
    215         ONLY:  constant_diffusion, dissipation_1d, humidity,                   &
    216                intermediate_timestep_count, intermediate_timestep_count_max,   &
    217                f, g, ibc_e_b, kappa, mixing_length_1d, passive_scalar,         &
    218                prandtl_layer, rif_max, rif_min, simulated_time_chr,            &
    219                timestep_scheme, tsc
     216        ONLY:  constant_diffusion, constant_flux_layer, dissipation_1d,        &
     217               humidity, intermediate_timestep_count,                          &
     218               intermediate_timestep_count_max, f, g, ibc_e_b, kappa,          & 
     219               mixing_length_1d, passive_scalar,                               &
     220               simulated_time_chr, timestep_scheme, tsc, zeta_max, zeta_min
    220221               
    221222    USE indices,                                                               &
     
    334335!--       Finite differences of the momentum fluxes are computed using half the
    335336!--       normal grid length (2.0*ddzw(k)) for the sake of enhanced accuracy
    336           IF ( prandtl_layer )  THEN
     337          IF ( constant_flux_layer )  THEN
    337338
    338339             k = nzb+1
     
    465466!
    466467!--          First compute the vertical fluxes in the Prandtl-layer
    467              IF ( prandtl_layer )  THEN
     468             IF ( constant_flux_layer )  THEN
    468469!
    469470!--             Compute theta* using Rif numbers of the previous time step
     
    498499                ENDIF
    499500
    500              ENDIF    ! prandtl_layer
     501             ENDIF    ! constant_flux_layer
    501502
    502503!
     
    506507!--          the rif-numbers of the previous time step are used.
    507508
    508              IF ( prandtl_layer )  THEN
     509             IF ( constant_flux_layer )  THEN
    509510                IF ( .NOT. humidity )  THEN
    510511                   pt_0 = pt_init(nzb+1)
     
    547548!--          range. It is exceeded excessively for very small velocities
    548549!--          (u,v --> 0).
    549              WHERE ( rif1d < rif_min )  rif1d = rif_min
    550              WHERE ( rif1d > rif_max )  rif1d = rif_max
     550             WHERE ( rif1d < zeta_min )  rif1d = zeta_min
     551             WHERE ( rif1d > zeta_max )  rif1d = zeta_max
    551552
    552553!
    553554!--          Compute u* from the absolute velocity value
    554              IF ( prandtl_layer )  THEN
     555             IF ( constant_flux_layer )  THEN
    555556                uv_total = SQRT( u1d(nzb+1)**2 + v1d(nzb+1)**2 )
    556557
     
    639640                ENDIF             
    640641
    641              ENDIF   !  prandtl_layer
     642             ENDIF   !  constant_flux_layer
    642643
    643644!
     
    673674!--          computed via the adiabatic mixing length, for the unstability has
    674675!--          already been taken account of via the TKE (cf. also Diss.).
    675              IF ( prandtl_layer )  THEN
     676             IF ( constant_flux_layer )  THEN
    676677                IF ( rif1d(nzb+1) >= 0.0_wp )  THEN
    677678                   km1d(nzb+1) = us1d * kappa * zu(nzb+1) /                    &
     
    805806
    806807       uv_total = SQRT( u1d(nzb+1)**2 + v1d(nzb+1)**2 )
    807        IF ( ABS( v1d(nzb+1) ) .LT. 1.0E-5_wp )  THEN
     808       IF ( ABS( v1d(nzb+1) ) < 1.0E-5_wp )  THEN
    808809          alpha = ACOS( SIGN( 1.0_wp , u1d(nzb+1) ) )
    809810       ELSE
Note: See TracChangeset for help on using the changeset viewer.