Changeset 4880 for palm/trunk/SOURCE/netcdf_data_input_mod.f90
- Timestamp:
- Feb 18, 2021 12:08:41 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r4878 r4880 24 24 ! ----------------- 25 25 ! $Id$ 26 ! Minor formatting adjustments and some comments added in get_variable_surf 27 ! 28 ! 4878 2021-02-18 09:47:49Z suehring 26 29 ! Rename resize_array into add_ghost_layers; remove number of passed indices; replace subroutine 27 30 ! calls with interface name … … 4190 4193 4191 4194 USE grid_variables, & 4192 ONLY: d x,dy4195 ONLY: ddx, ddy 4193 4196 4194 4197 USE basic_constants_and_equations_mod, & … … 4202 4205 CHARACTER(LEN=*) :: variable_name !< variable name 4203 4206 4204 INTEGER(iwp) :: i, j 4207 INTEGER(iwp) :: i !< grid index in x-direction 4208 INTEGER(iwp) :: j !< grid index in y-direction 4205 4209 INTEGER(iwp), INTENT(IN) :: id !< file id 4206 4210 INTEGER(iwp) :: id_azimuth !< azimuth variable id … … 4215 4219 INTEGER(iwp) :: nsurf !< total number of surfaces in file 4216 4220 4217 INTEGER(iwp), DIMENSION(6) :: coords !< integer coordinates of surface 4221 INTEGER(iwp), DIMENSION(6) :: coords !< integer coordinates of surface location 4218 4222 INTEGER(iwp), DIMENSION(2) :: id_dim !< dimension ids 4219 4223 … … 4224 4228 REAL(wp), DIMENSION(:), ALLOCATABLE :: azimuth !< read buffer for azimuth(s) 4225 4229 REAL(wp), DIMENSION(:), ALLOCATABLE :: zenith !< read buffer for zenith(s) 4226 REAL(wp), DIMENSION(:), ALLOCATABLE :: zs, ys, xs !< read buffer for zs(s), ys, xs 4227 4228 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: pars_read !< read buffer 4230 REAL(wp), DIMENSION(:), ALLOCATABLE :: xs !< surface coordinate array of x-dimension 4231 REAL(wp), DIMENSION(:), ALLOCATABLE :: ys !< surface coordinate array of y-dimension 4232 REAL(wp), DIMENSION(:), ALLOCATABLE :: zs !< surface coordinate array of z-dimension 4233 4234 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: pars_read !< read buffer for the building parameters 4229 4235 4230 4236 TYPE(pars_surf) :: surf !< parameters variable to be loaded … … 4233 4239 #if defined( __netcdf ) 4234 4240 ! 4235 !-- First, inquire variable ID 4241 !-- First, inquire variable ID's 4236 4242 nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 4237 4243 nc_stat = NF90_INQ_VARID( id, 'zs', id_zs ) … … 4241 4247 nc_stat = NF90_INQ_VARID( id, 'azimuth', id_azimuth ) 4242 4248 ! 4243 !-- Inquire dimension sizes 4249 !-- Inquire dimension sizes for the number of surfaces and parameters given 4244 4250 nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim ) 4245 4251 nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = nsurf ) … … 4250 4256 xs(nsurf_pars_read), zenith(nsurf_pars_read), & 4251 4257 azimuth(nsurf_pars_read), & 4252 nsurf_ji(nys:nyn, 4258 nsurf_ji(nys:nyn,nxl:nxr) ) 4253 4259 4254 4260 nsurf_ji(:,:) = 0 4255 4261 ! 4256 !-- Scan surface coordinates, count local 4262 !-- Scan surface coordinates, count locally 4257 4263 is0 = 1 4258 4264 DO … … 4281 4287 coords(3) < nxl .OR. coords(3) > nxr ) CYCLE 4282 4288 4283 nsurf_ji(coords(2), coords(3)) = nsurf_ji(coords(2),coords(3)) + 14289 nsurf_ji(coords(2),coords(3)) = nsurf_ji(coords(2),coords(3)) + 1 4284 4290 ENDDO 4285 4291 is0 = is0 + isc … … 4287 4293 ! 4288 4294 !-- Populate reverse index from surface counts 4289 ALLOCATE( surf%index_ji( 2, nys:nyn,nxl:nxr ) )4295 ALLOCATE( surf%index_ji( 2,nys:nyn,nxl:nxr ) ) 4290 4296 isurf = 1 4291 4297 DO j = nys, nyn … … 4297 4303 4298 4304 surf%nsurf = isurf - 1 4299 ALLOCATE( surf%pars( 0:surf%np-1, surf%nsurf ),&4300 surf%coords( 6, surf%nsurf) )4305 ALLOCATE( surf%pars(0:surf%np-1,surf%nsurf), & 4306 surf%coords(6,surf%nsurf) ) 4301 4307 ! 4302 4308 !-- Scan surfaces again, saving pars into allocated structures … … 4337 4343 !-- Determine maximum terrain under building (base z-coordinate). Using normal vector to 4338 4344 !-- locate building inner coordinates. 4339 oro_max_l = buildings_f%oro_max(coords(2)-coords(5), 4345 oro_max_l = buildings_f%oro_max(coords(2)-coords(5),coords(3)-coords(6)) 4340 4346 IF ( oro_max_l == buildings_f%fill1 ) THEN 4341 4347 WRITE( message_string, * ) 'Found building surface on ' // & … … 4351 4357 ! 4352 4358 !-- Save surface entry 4353 is = surf%index_ji(1, coords(2), coords(3)) + nsurf_ji(coords(2),coords(3))4359 is = surf%index_ji(1,coords(2),coords(3)) + nsurf_ji(coords(2),coords(3)) 4354 4360 surf%pars(:,is) = pars_read(isurf,:) 4355 4361 surf%coords(:,is) = coords(:) 4356 4362 4357 nsurf_ji(coords(2), coords(3)) = nsurf_ji(coords(2),coords(3)) + 14363 nsurf_ji(coords(2),coords(3)) = nsurf_ji(coords(2),coords(3)) + 1 4358 4364 ENDDO 4359 4365 … … 4370 4376 4371 4377 REAL(wp), INTENT(in) :: azimuth !< surface normal azimuth angle in degrees 4372 REAL(wp), INTENT(in) :: x, y !< surface centre coordinates in metres from origin 4378 REAL(wp), INTENT(in) :: x !< surface centre coordinate in x in metres from origin 4379 REAL(wp), INTENT(in) :: y !< surface centre coordinate in y in metres from origin 4373 4380 REAL(wp), INTENT(in) :: zenith !< surface normal zenith angle in degrees 4374 4381 … … 4383 4390 4384 4391 transform_coords(1) = -999.0_wp ! not calculated here 4385 transform_coords(2) = NINT( y /dy - 0.5_wp + 0.5_wp * transform_coords(5), KIND=iwp )4386 transform_coords(3) = NINT( x /dx - 0.5_wp + 0.5_wp * transform_coords(6), KIND=iwp )4392 transform_coords(2) = NINT( y * ddy - 0.5_wp + 0.5_wp * transform_coords(5), KIND=iwp ) 4393 transform_coords(3) = NINT( x * ddx - 0.5_wp + 0.5_wp * transform_coords(6), KIND=iwp ) 4387 4394 4388 4395 END FUNCTION transform_coords
Note: See TracChangeset
for help on using the changeset viewer.