Changeset 4168 for palm/trunk/SOURCE/biometeorology_mod.f90
- Timestamp:
- Aug 16, 2019 1:50:17 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/biometeorology_mod.f90
r4144 r4168 27 27 ! ----------------- 28 28 ! $Id$ 29 ! Replace function get_topography_top_index by topo_top_ind 30 ! 31 ! 4144 2019-08-06 09:11:47Z raasch 29 32 ! relational operators .EQ., .NE., etc. replaced by ==, /=, etc. 30 33 ! … … 178 181 USE indices, & 179 182 ONLY: nxl, nxr, nys, nyn, nzb, nzt, nys, nyn, nxl, nxr, nxlg, nxrg, & 180 nysg, nyng 183 nysg, nyng, topo_top_ind 181 184 182 185 USE kinds !< Set precision of INTEGER and REAL arrays according to PALM … … 192 195 radiation_interactions, rad_sw_in, & 193 196 rad_sw_out, rad_lw_in, rad_lw_out 194 195 USE surface_mod, &196 ONLY: get_topography_top_index_ji197 197 198 198 IMPLICIT NONE … … 1557 1557 j = mrtbl(iy,l) 1558 1558 k = mrtbl(iz,l) 1559 IF ( k - get_topography_top_index_ji( j, i, 's' ) == & 1560 bio_cell_level + 1_iwp) THEN 1559 IF ( k - topo_top_ind(j,i,0) == bio_cell_level + 1_iwp) THEN 1561 1560 ! 1562 1561 !-- Averaging was done before, so we can just copy the result here … … 1583 1582 j = mrtbl(iy,l) 1584 1583 k = mrtbl(iz,l) 1585 IF ( k - get_topography_top_index_ji( j, i, 's' ) == & 1586 bio_cell_level + 1_iwp) THEN 1584 IF ( k - topo_top_ind(j,i,0) == bio_cell_level + 1_iwp) THEN 1587 1585 IF ( mrt_include_sw ) THEN 1588 1586 tmrt_grid(j,i) = ( ( human_absorb * mrtinsw(l) + & … … 1608 1606 !------------------------------------------------------------------------------! 1609 1607 SUBROUTINE bio_get_thermal_index_input_ij( average_input, i, j, ta, vp, ws, & 1610 pair, tmrt )1608 pair, tmrt ) 1611 1609 1612 1610 IMPLICIT NONE … … 1633 1631 !-- Determine cell level closest to 1.1m above ground 1634 1632 ! by making use of truncation due to int cast 1635 k = INT( get_topography_top_index_ji(j, i, 's') + bio_cell_level ) !< Vertical cell center closest to 1.1m1633 k = INT( topo_top_ind(j,i,0) + bio_cell_level ) !< Vertical cell center closest to 1.1m 1636 1634 1637 1635 !
Note: See TracChangeset
for help on using the changeset viewer.