Ignore:
Timestamp:
Nov 21, 2019 3:59:16 PM (4 years ago)
Author:
suehring
Message:

Bugfixes: Calculation of 2-m temperature adjusted to the case the 2-m level is above the first grid level; salsa: close netcdf input files after reading; open netcdf input files with read-only attribute instead of write attribute

File:
1 edited

Legend:

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

    r4258 r4298  
    2626! -----------------
    2727! $Id$
     28! Calculation of 2-m temperature adjusted to the case the 2-m level is above
     29! the first grid point.
     30!
     31! 4258 2019-10-07 13:29:08Z suehring
    2832! Initialization of Obukhov lenght also at vertical surfaces (if allocated).
    2933!
     
    105109               debug_output_timestep,                                          &
    106110               do_output_at_2m, humidity,                                      &
    107                ibc_e_b, ibc_pt_b, indoor_model, initializing_actions,          &
    108                intermediate_timestep_count, intermediate_timestep_count_max,   &
     111               ibc_e_b, ibc_pt_b, indoor_model,                                &
    109112               land_surface, large_scale_forcing, lsf_surf, message_string,    &
    110113               neutral, passive_scalar, pt_surface, q_surface,                 &
    111                run_coupled, surface_pressure, simulated_time, terminate_run,   &
     114               run_coupled, surface_pressure, simulated_time,                  &
    112115               time_since_reference_point, urban_surface,                      &
    113116               use_free_convection_scaling, zeta_max, zeta_min
     
    117120
    118121    USE indices,                                                               &
    119         ONLY:  nxl, nxr, nys, nyn, nzb
     122        ONLY:  nzt
    120123
    121124    USE kinds
     
    18561859       IMPLICIT NONE
    18571860
    1858        CHARACTER (LEN = *), INTENT(IN)       :: z_char       !< string identifier to identify z level
    1859        INTEGER(iwp)                          :: i, j, k, m   !< running indices
     1861       CHARACTER (LEN = *), INTENT(IN) :: z_char !< string identifier to identify z level
     1862       INTEGER(iwp)                    :: i      !< grid index x-dimension
     1863       INTEGER(iwp)                    :: j      !< grid index y-dimension
     1864       INTEGER(iwp)                    :: k      !< grid index z-dimension
     1865       INTEGER(iwp)                    :: kk     !< running index along the z-dimension
     1866       INTEGER(iwp)                    :: m      !< running index for surface elements
    18601867
    18611868       
     
    18731880                surf%pt_10cm(m) = surf%pt_surface(m) + surf%ts(m) / kappa      &
    18741881                                   * ( LOG( 0.1_wp /  surf%z0h(m) )            &
    1875                                   - psi_h( 0.1_wp / surf%ol(m) )               &
     1882                                     - psi_h( 0.1_wp / surf%ol(m) )            &
    18761883                                     + psi_h( surf%z0h(m) / surf%ol(m) ) )
    18771884                                   
    18781885             ENDDO
    18791886
    1880 
     1887!
     1888!--       2-m temperature. Note, this is only calculated for output reasons at
     1889!--       horizontal upward-facing surfaces.
    18811890          CASE ( '2m' )
    18821891     
     
    18861895                j = surf%j(m)
    18871896                k = surf%k(m)
    1888 
    1889                 surf%pt_2m(m) = surf%pt_surface(m) + surf%ts(m) / kappa        &
     1897!
     1898!--             If 2-m level is below the first grid level, MOST is
     1899!--             used for calculation of 2-m temperature.
     1900                IF ( surf%z_mo(m) > 2.0_wp )  THEN
     1901                   surf%pt_2m(m) = surf%pt_surface(m) + surf%ts(m) / kappa     &
    18901902                                   * ( LOG( 2.0_wp /  surf%z0h(m) )            &
    18911903                                     - psi_h( 2.0_wp / surf%ol(m) )            &
    18921904                                     + psi_h( surf%z0h(m) / surf%ol(m) ) )
     1905!
     1906!--             If 2-m level is above the first grid level, 2-m temperature
     1907!--             is linearly interpolated between the two nearest vertical grid
     1908!--             levels. Note, since 2-m temperature is only computed for
     1909!--             horizontal upward-facing surfaces, only a vertical
     1910!--             interpolation is necessary.
     1911                ELSE
     1912!
     1913!--                zw(k-1) defines the height of the surface.
     1914                   kk = k
     1915                   DO WHILE ( zu(kk) - zw(k-1) < 2.0_wp  .AND.  kk <= nzt )
     1916                      kk = kk + 1
     1917                   ENDDO               
     1918!
     1919!--                kk defines the index of the first grid level >= 2m.
     1920                   surf%pt_2m(m) = pt(kk-1,j,i) +                              &
     1921                                 ( zw(k-1) + 2.0_wp - zu(kk-1)     ) *         &
     1922                                 ( pt(kk,j,i)       - pt(kk-1,j,i) ) /         &
     1923                                 ( zu(kk)           - zu(kk-1)     )
     1924                ENDIF
    18931925
    18941926             ENDDO
Note: See TracChangeset for help on using the changeset viewer.