Ignore:
Timestamp:
Oct 29, 2019 2:34:15 PM (5 years ago)
Author:
monakurppa
Message:

Correct recent bugs in salsa_mod and remove chemistry specific stuff in netcdf_data_iput_mod

  • A boundary conditions bug in salsa_mod: set top boundary to its default value (neumann) if nesting is turned off
  • In salsa_nesting_offl_bc, correct fac_dt to apply time_utc_init
  • Remove chemistry specific parts (inside an if clause id==id_emis) in get_variable_4d_to_3d_real and get_variable_5d_to_4d_real
File:
1 edited

Legend:

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

    r4258 r4280  
    2525! -----------------
    2626! $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
    2731! - Migrate input of soil temperature and moisture to land-surface model.
    2832! - Remove interpolate routines and move the only required subroutine to
     
    52335237       CHARACTER(LEN=*)              ::  variable_name   !< variable name
    52345238
    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 n
    5236 
    52375239       INTEGER(iwp)                  ::  i               !< index along x direction
    52385240       INTEGER(iwp)                  ::  ie              !< end index for subdomain input along x direction
     
    52465248       INTEGER(iwp)                  ::  ke              !< end index of 4th dimension
    52475249       INTEGER(iwp)                  ::  ks              !< start index of 4th dimension
    5248        
     5250       INTEGER(iwp)                  ::  ns              !< start index for subdomain input along n dimension
     5251
    52495252       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
    52505253                                                         !< to its reverse memory access
    52515254
    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
    52535257#if defined( __netcdf )
    52545258
    52555259!
    52565260!--    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 )
    52585262!
    52595263!--    Check for collective read-operation and set respective NetCDF flags if
     
    52625266          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
    52635267       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)
    53005284             ENDDO
    53015285          ENDDO
    5302 
    5303          DEALLOCATE( tmp )
    5304 
    5305        ENDIF
     5286       ENDDO
     5287
     5288      DEALLOCATE( tmp )
     5289
    53065290#endif
    53075291    END SUBROUTINE get_variable_4d_to_3d_real
     
    54355419       INTEGER(iwp)                  ::  ke              !< end index of 5th dimension
    54365420       INTEGER(iwp)                  ::  ks              !< start index of 5th dimension
    5437        
     5421
    54385422       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
    54395423                                                           ! to its reverse memory access
     
    54495433          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
    54505434       ENDIF
    5451 
    5452       !Temporary solution for reading emission chemistry files:
    5453        IF ( id == id_emis ) THEN
    5454 
    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 variable
    5459           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=tmp
    5464 
    5465           CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name )
    5466  
    5467           DEALLOCATE( tmp )
    5468 
    5469        !>  Original Subroutine part
    5470        ELSE
    54715435!
    54725436!--    Allocate temporary variable according to memory access on file.
    5473           ALLOCATE( tmp(ks:ke,js:je,is:is,ts:te) )
     5437       ALLOCATE( tmp(ks:ke,js:je,is:is,ts:te) )
    54745438!
    54755439!--    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)
    54905453                ENDDO
    54915454             ENDDO
    5492           ENDDO
    5493 
    5494           DEALLOCATE( tmp )
    5495 
    5496        ENDIF
     5455          ENDDO
     5456       ENDDO
     5457
     5458       DEALLOCATE( tmp )
    54975459#endif
    54985460    END SUBROUTINE get_variable_5d_to_4d_real
Note: See TracChangeset for help on using the changeset viewer.