Changeset 4280 for palm/trunk/SOURCE/netcdf_data_input_mod.f90
- Timestamp:
- Oct 29, 2019 2:34:15 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r4258 r4280 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Remove id_emis flags from get_variable_4d_to_3d_real and 28 ! get_variable_5d_to_4d_real 29 ! 30 ! 4258 2019-10-07 13:29:08Z suehring 27 31 ! - Migrate input of soil temperature and moisture to land-surface model. 28 32 ! - Remove interpolate routines and move the only required subroutine to … … 5233 5237 CHARACTER(LEN=*) :: variable_name !< variable name 5234 5238 5235 INTEGER(iwp) :: ns !< start index for subdomain input along n dimension: ns coincides here with ne, since, we select only one value along the 1st dimension n5236 5237 5239 INTEGER(iwp) :: i !< index along x direction 5238 5240 INTEGER(iwp) :: ie !< end index for subdomain input along x direction … … 5246 5248 INTEGER(iwp) :: ke !< end index of 4th dimension 5247 5249 INTEGER(iwp) :: ks !< start index of 4th dimension 5248 5250 INTEGER(iwp) :: ns !< start index for subdomain input along n dimension 5251 5249 5252 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: tmp !< temporary variable to read data from file according 5250 5253 !< to its reverse memory access 5251 5254 5252 REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) :: var !< variable where the read data have to be stored: one dimension is reduced in the process 5255 REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) :: var !< variable where the read data have to be stored: 5256 !< one dimension is reduced in the process 5253 5257 #if defined( __netcdf ) 5254 5258 5255 5259 ! 5256 5260 !-- Inquire variable id 5257 nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 5261 nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 5258 5262 ! 5259 5263 !-- Check for collective read-operation and set respective NetCDF flags if … … 5262 5266 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 5263 5267 ENDIF 5264 5265 !Temporary solution for reading emission chemistry files: 5266 IF ( id == id_emis ) THEN 5267 5268 !-- Allocate temporary variable according to memory access on file. 5269 ALLOCATE( tmp(is:ie,js:je,ks:ke) ) 5270 5271 !-- Get variable 5272 nc_stat = NF90_GET_VAR( id, id_var, tmp(is:ie,js:je,ks:ke), & 5273 start = (/ ns, is, js+1, ks+1 /), & 5274 count = (/ 1, ie-is+1 , je-js+1, ke-ks+1 /) ) 5275 5276 var=tmp(:,:,:) 5277 5278 CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name ) 5279 5280 DEALLOCATE( tmp ) 5281 5282 ELSE 5283 ! 5284 !-- Allocate temporary variable according to memory access on file. 5285 ALLOCATE( tmp(is:ie,js:je,ks:ke) ) 5286 ! 5287 !-- Get variable 5288 nc_stat = NF90_GET_VAR( id, id_var, tmp, & 5289 start = (/ is+1, js+1, ks+1, ns+1 /),& 5290 count = (/ ie-is+1, je-js+1, ke-ks+1, 1 /) ) 5291 5292 CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name ) 5293 ! 5294 !-- Resort data. Please note, dimension subscripts of var all start at 1. 5295 DO i = is, ie 5296 DO j = js, je 5297 DO k = ks, ke 5298 var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k) 5299 ENDDO 5268 ! 5269 !-- Allocate temporary variable according to memory access on file. 5270 ALLOCATE( tmp(is:ie,js:je,ks:ke) ) 5271 ! 5272 !-- Get variable 5273 nc_stat = NF90_GET_VAR( id, id_var, tmp, & 5274 start = (/ is+1, js+1, ks+1, ns+1 /), & 5275 count = (/ ie-is+1, je-js+1, ke-ks+1, 1 /) ) 5276 5277 CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name ) 5278 ! 5279 !-- Resort data. Please note, dimension subscripts of var all start at 1. 5280 DO i = is, ie 5281 DO j = js, je 5282 DO k = ks, ke 5283 var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k) 5300 5284 ENDDO 5301 5285 ENDDO 5302 5303 DEALLOCATE( tmp ) 5304 5305 ENDIF 5286 ENDDO 5287 5288 DEALLOCATE( tmp ) 5289 5306 5290 #endif 5307 5291 END SUBROUTINE get_variable_4d_to_3d_real … … 5435 5419 INTEGER(iwp) :: ke !< end index of 5th dimension 5436 5420 INTEGER(iwp) :: ks !< start index of 5th dimension 5437 5421 5438 5422 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tmp !< temporary variable to read data from file according 5439 5423 ! to its reverse memory access … … 5449 5433 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 5450 5434 ENDIF 5451 5452 !Temporary solution for reading emission chemistry files:5453 IF ( id == id_emis ) THEN5454 5455 !-- Allocate temporary variable according to memory access on file.5456 ALLOCATE( tmp(ts:te,1,js+1:je+1,ks+1:ke+1) )5457 5458 !-- Get variable5459 nc_stat = NF90_GET_VAR( id, id_var, tmp(ts:te,1,js+1:je+1,ks+1:ke+1), &5460 start = (/ ns, ts, 1, js+1, ks+1 /), &5461 count = (/ 1, te-ts+1, 1, je-js+1, ke-ks+1 /) )5462 5463 var=tmp5464 5465 CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name )5466 5467 DEALLOCATE( tmp )5468 5469 !> Original Subroutine part5470 ELSE5471 5435 ! 5472 5436 !-- Allocate temporary variable according to memory access on file. 5473 5437 ALLOCATE( tmp(ks:ke,js:je,is:is,ts:te) ) 5474 5438 ! 5475 5439 !-- Get variable 5476 nc_stat = NF90_GET_VAR( id, id_var, tmp, & 5477 start = (/ ks+1, js+1, is+1, ts+1, ns /), & 5478 count = (/ ke-ks+1, je-js+1, ie-is+1, te-ts+1, 1 /) ) 5479 5480 CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name ) 5481 ! 5482 !-- Resort data. Please note, dimension subscripts of var all start at 1. 5483 5484 DO t = ts, te 5485 DO i = is, ie 5486 DO j = js, je 5487 DO k = ks, ke 5488 var(t-ts+1,i-is+1,j-js+1,k-ks+1) = tmp(k,j,i,t) 5489 ENDDO 5440 nc_stat = NF90_GET_VAR( id, id_var, tmp, & 5441 start = (/ ks+1, js+1, is+1, ts+1, ns /), & 5442 count = (/ ke-ks+1, je-js+1, ie-is+1, te-ts+1, 1 /) ) 5443 5444 CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name ) 5445 ! 5446 !-- Resort data. Please note, dimension subscripts of var all start at 1. 5447 5448 DO t = ts, te 5449 DO i = is, ie 5450 DO j = js, je 5451 DO k = ks, ke 5452 var(t-ts+1,i-is+1,j-js+1,k-ks+1) = tmp(k,j,i,t) 5490 5453 ENDDO 5491 5454 ENDDO 5492 ENDDO 5493 5494 DEALLOCATE( tmp ) 5495 5496 ENDIF 5455 ENDDO 5456 ENDDO 5457 5458 DEALLOCATE( tmp ) 5497 5459 #endif 5498 5460 END SUBROUTINE get_variable_5d_to_4d_real
Note: See TracChangeset
for help on using the changeset viewer.