Changeset 3933 for palm/trunk/SOURCE/land_surface_model_mod.f90
- Timestamp:
- Apr 25, 2019 12:33:20 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/land_surface_model_mod.f90
r3885 r3933 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Remove unused subroutine and allocation of pt_2m, this is done in surface_mod 28 ! now (surfaces%pt_2m) 29 ! 30 ! 27 31 ! Changes related to global restructuring of location messages and introduction 28 32 ! of additional debug messages … … 1017 1021 !-- Public functions 1018 1022 PUBLIC lsm_boundary_condition, lsm_check_data_output, & 1019 lsm_check_data_output_pr, lsm_calc_pt_near_surface,&1023 lsm_check_data_output_pr, & 1020 1024 lsm_check_parameters, lsm_define_netcdf_grid, lsm_3d_data_averaging,& 1021 1025 lsm_data_output_2d, lsm_data_output_3d, lsm_energy_balance, & … … 1038 1042 END INTERFACE lsm_boundary_condition 1039 1043 1040 INTERFACE lsm_calc_pt_near_surface1041 MODULE PROCEDURE lsm_calc_pt_near_surface1042 END INTERFACE lsm_calc_pt_near_surface1043 1044 1044 INTERFACE lsm_check_data_output 1045 1045 MODULE PROCEDURE lsm_check_data_output … … 5057 5057 ALLOCATE ( surf_lsm_h%r_s(1:surf_lsm_h%ns) ) 5058 5058 ALLOCATE ( surf_lsm_h%r_canopy_min(1:surf_lsm_h%ns) ) 5059 ALLOCATE ( surf_lsm_h%pt_2m(1:surf_lsm_h%ns) )5060 5059 ALLOCATE ( surf_lsm_h%vegetation_surface(1:surf_lsm_h%ns) ) 5061 5060 ALLOCATE ( surf_lsm_h%water_surface(1:surf_lsm_h%ns) ) … … 7322 7321 END SUBROUTINE calc_z0_water_surface 7323 7322 7324 7325 !------------------------------------------------------------------------------!7326 ! Description:7327 ! ------------7328 !> Calculates 2m temperature for data output at coarse resolution7329 !------------------------------------------------------------------------------!7330 SUBROUTINE lsm_calc_pt_near_surface7331 7332 IMPLICIT NONE7333 7334 INTEGER(iwp) :: i, j, k, m !< running indices7335 7336 7337 DO m = 1, surf_lsm_h%ns7338 7339 i = surf_lsm_h%i(m)7340 j = surf_lsm_h%j(m)7341 k = surf_lsm_h%k(m)7342 7343 surf_lsm_h%pt_2m(m) = surf_lsm_h%pt_surface(m) + surf_lsm_h%ts(m) / kappa &7344 * ( log( 2.0_wp / surf_lsm_h%z0h(m) ) &7345 - psi_h( 2.0_wp / surf_lsm_h%ol(m) ) &7346 + psi_h( surf_lsm_h%z0h(m) / surf_lsm_h%ol(m) ) )7347 7348 ENDDO7349 7350 END SUBROUTINE lsm_calc_pt_near_surface7351 7352 7353 7354 7323 ! 7355 7324 !-- Integrated stability function for heat and moisture
Note: See TracChangeset
for help on using the changeset viewer.