Ignore:
Timestamp:
May 22, 2019 5:27:26 PM (5 years ago)
Author:
suehring
Message:

Rename the USM-internal flag spinup into during_spinup, in order to avoid confusion with global control parameter

File:
1 edited

Legend:

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

    r3987 r3993  
    2828! -----------------
    2929! $Id$
     30! In order to avoid confusion with global control parameter, rename the
     31! USM-internal flag spinup into during_spinup.
     32!
     33! 3987 2019-05-22 09:52:13Z kanani
    3034! Introduce alternative switch for debug output during timestepping
    3135!
     
    498502               timestep_scheme, tsc, coupling_char, io_blocks, io_group,       &
    499503               message_string, time_since_reference_point, surface_pressure,   &
    500                pt_surface, large_scale_forcing, lsf_surf, spinup,              &
     504               pt_surface, large_scale_forcing, lsf_surf,                      &
    501505               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
    502506               average_count_3d, varnamelength, urban_surface, dz
     
    52565260!> possible timestep.
    52575261!------------------------------------------------------------------------------!
    5258     SUBROUTINE usm_material_heat_model( spinup )
     5262    SUBROUTINE usm_material_heat_model( during_spinup )
    52595263
    52605264
     
    52675271        REAL(wp), DIMENSION(nzb_wall:nzt_wall) :: wall_mod
    52685272
    5269         LOGICAL      :: spinup  !< if true, no calculation of window temperatures
     5273        LOGICAL      :: during_spinup  !< if true, no calculation of window temperatures
    52705274
    52715275
    52725276        IF ( debug_output_timestep )  THEN
    5273            WRITE( debug_string, * ) 'usm_material_heat_model | spinup: ', spinup
     5277           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
     5278                                     during_spinup
    52745279           CALL debug_message( debug_string, 'start' )
    52755280        ENDIF
     
    52775282        !$OMP PARALLEL PRIVATE (m, i, j, k, kw, wtend, wintend, win_absorp, wall_mod)
    52785283        wall_mod=1.0_wp
    5279         IF (usm_wall_mod .AND. spinup) THEN
     5284        IF ( usm_wall_mod  .AND.  during_spinup ) THEN
    52805285           DO  kw=nzb_wall,nzb_wall+1
    52815286               wall_mod(kw)=0.1_wp
     
    53565361!
    53575362!-- during spinup the tempeature inside window layers is not calculated to make larger timesteps possible
    5358            IF ( .NOT. spinup) THEN
     5363           IF ( .NOT. during_spinup ) THEN
    53595364              win_absorp = -log(surf_usm_h%transmissivity(m)) / surf_usm_h%zw_window(nzt_wall,m)
    53605365!
     
    54445449           ENDIF
    54455450
    5446            IF (.NOT. spinup) THEN
     5451           IF ( .NOT. during_spinup ) THEN
    54475452!
    54485453!--           calculate t_window tendencies for the next Runge-Kutta step
     
    55375542                                 * surf_usm_v(l)%tt_wall_m(nzb_wall:nzt_wall,m) )   
    55385543
    5539               IF (.NOT. spinup) THEN
     5544              IF ( .NOT. during_spinup ) THEN
    55405545                 win_absorp = -log(surf_usm_v(l)%transmissivity(m)) / surf_usm_v(l)%zw_window(nzt_wall,m)
    55415546!
     
    56245629
    56255630
    5626               IF (.NOT. spinup) THEN
     5631              IF ( .NOT. during_spinup ) THEN
    56275632!
    56285633!--              calculate t_window tendencies for the next Runge-Kutta step
     
    56485653
    56495654        IF ( debug_output_timestep )  THEN
    5650            WRITE( debug_string, * ) 'usm_material_heat_model | spinup: ', spinup
     5655           WRITE( debug_string, * ) 'usm_material_heat_model | during_spinup: ',&
     5656                                    during_spinup
    56515657           CALL debug_message( debug_string, 'end' )
    56525658        ENDIF
     
    76517657!> maximum possible timstep
    76527658!------------------------------------------------------------------------------!
    7653     SUBROUTINE usm_surface_energy_balance( spinup )
     7659    SUBROUTINE usm_surface_energy_balance( during_spinup )
    76547660
    76557661
     
    76627668        INTEGER(iwp) ::  k_off     !< offset to determine index of surface element, seen from atmospheric grid point, for z
    76637669
    7664         LOGICAL                               :: spinup             !true during spinup
     7670        LOGICAL                               :: during_spinup      !< flag indicating soil/wall spinup phase
    76657671       
    76667672        REAL(wp)                              :: frac_win           !< window fraction, used to restore original values during spinup
     
    77117717
    77127718        IF ( debug_output_timestep )  THEN
    7713            WRITE( debug_string, * ) 'usm_surface_energy_balance | spinup: ', spinup
     7719           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
     7720                                    during_spinup
    77147721           CALL debug_message( debug_string, 'start' )
    77157722        ENDIF
     
    77357742!--       at the end of the loop.
    77367743!--       Note, this is a temporary fix and need to be removed later. 
    7737            IF ( spinup )  THEN
     7744           IF ( during_spinup )  THEN
    77387745              frac_win   = surf_usm_h%frac(ind_wat_win,m)
    77397746              frac_wall  = surf_usm_h%frac(ind_veg_wall,m)
     
    79277934                                       f_shf * surf_usm_h%pt1(m) +             &
    79287935                                       lambda_surface * t_wall_h(nzb_wall,m)
    7929            IF ( ( .NOT. spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
     7936           IF ( ( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
    79307937              coef_window_1 = surf_usm_h%rad_net_l(m) +                           &
    79317938                      ( 3.0_wp + 1.0_wp ) * surf_usm_h%emissivity(ind_wat_win,m)  &
     
    79537960                             sigma_sb * t_surf_wall_h(m) ** 3                  &
    79547961                           + lambda_surface + f_shf / exner(k)
    7955            IF ( ( .NOT. spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
     7962           IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_h%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
    79567963              coef_window_2 = 4.0_wp * surf_usm_h%emissivity(ind_wat_win,m) *     &
    79577964                                sigma_sb * t_surf_window_h(m) ** 3                &
     
    79737980                             surf_usm_h%c_surface(m) * t_surf_wall_h(m) ) /        &
    79747981                           ( surf_usm_h%c_surface(m) + coef_2 * dt_3d * tsc(2) )
    7975            IF ((.NOT. spinup).AND.(surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
     7982           IF (( .NOT. during_spinup ) .AND. (surf_usm_h%frac(ind_wat_win,m) > 0.0_wp)) THEN
    79767983              t_surf_window_h_p(m) = ( coef_window_1 * dt_3d * tsc(2) +                        &
    79777984                                surf_usm_h%c_surface_window(m) * t_surf_window_h(m) ) /        &
     
    81878194!--        During spinup green and window fraction are set to zero. Here, the original
    81888195!--        values are restored.
    8189            IF ( spinup )  THEN
     8196           IF ( during_spinup )  THEN
    81908197              surf_usm_h%frac(ind_wat_win,m)   = frac_win
    81918198              surf_usm_h%frac(ind_veg_wall,m)  = frac_wall
     
    82038210!--           at the end of the loop.
    82048211!--           Note, this is a temporary fix and need to be removed later.
    8205               IF ( spinup )  THEN
     8212              IF ( during_spinup )  THEN
    82068213                 frac_win   = surf_usm_v(l)%frac(ind_wat_win,m)
    82078214                 frac_wall  = surf_usm_v(l)%frac(ind_veg_wall,m)
     
    83668373                                      f_shf * surf_usm_v(l)%pt1(m) +            &
    83678374                                      lambda_surface * t_wall_v(l)%t(nzb_wall,m)
    8368               IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
     8375              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
    83698376                 coef_window_1 = surf_usm_v(l)%rad_net_l(m) +                   & ! coef +1 corresponds to -lwout
    83708377                                                                                  ! included in calculation of radnet_l
     
    83968403                                 t_surf_wall_v(l)%t(m) ** 3                             &
    83978404                               + lambda_surface + f_shf / exner(k) 
    8398               IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
     8405              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN             
    83998406                 coef_window_2 = 4.0_wp * surf_usm_v(l)%emissivity(ind_wat_win,m) * sigma_sb *       &
    84008407                                   t_surf_window_v(l)%t(m) ** 3                         &
     
    84168423                             surf_usm_v(l)%c_surface(m) * t_surf_wall_v(l)%t(m) ) / &
    84178424                             ( surf_usm_v(l)%c_surface(m) + coef_2 * dt_3d * tsc(2) )
    8418               IF ( ( .NOT. spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
     8425              IF ( ( .NOT. during_spinup ) .AND. ( surf_usm_v(l)%frac(ind_wat_win,m) > 0.0_wp ) ) THEN
    84198426                 t_surf_window_v_p(l)%t(m) = ( coef_window_1 * dt_3d * tsc(2) +                 &
    84208427                                surf_usm_v(l)%c_surface_window(m) * t_surf_window_v(l)%t(m) ) / &
     
    85848591!--           During spinup green and window fraction are set to zero. Here, the original
    85858592!--           values are restored.
    8586               IF ( spinup )  THEN
     8593              IF ( during_spinup )  THEN
    85878594                 surf_usm_v(l)%frac(ind_wat_win,m)   = frac_win
    85888595                 surf_usm_v(l)%frac(ind_veg_wall,m)  = frac_wall
     
    87578764
    87588765        IF ( debug_output_timestep )  THEN
    8759            WRITE( debug_string, * ) 'usm_surface_energy_balance | spinup: ', spinup
     8766           WRITE( debug_string, * ) 'usm_surface_energy_balance | during_spinup: ',&
     8767                                    during_spinup
    87608768           CALL debug_message( debug_string, 'end' )
    87618769        ENDIF
Note: See TracChangeset for help on using the changeset viewer.