Changeset 4387


Ignore:
Timestamp:
Jan 28, 2020 11:44:20 AM (4 years ago)
Author:
banzhafs
Message:

Added subroutine get_variable_string_generic to netcdf_data_input_mod

File:
1 edited

Legend:

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

    r4370 r4387  
    2020! Current revisions:
    2121! -----------------
    22 ! 
     22!
    2323!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! Added subroutine get_variable_string_generic ( )
     28! and added to interface get_variable to circumvent
     29! unknown application-specific restrictions
     30! in existing function get_variable_string ( ),
     31! which is retained for backward compatibility (ECC)
     32!
     33! 4370 2020-01-10 14:00:44Z raasch
    2734! collective read switched off on NEC Aurora to avoid hang situations
    28 ! 
     35!
    2936! 4362 2020-01-07 17:15:02Z suehring
    3037! Input of plant canopy variables from static driver moved to plant-canopy
     
    706713       MODULE PROCEDURE get_variable_5d_real_dynamic   ! 2B removed as z is out of emission_values
    707714       MODULE PROCEDURE get_variable_string
     715       MODULE PROCEDURE get_variable_string_generic    ! (ecc) generic string function
     716
    708717    END INTERFACE get_variable
    709718
     
    43624371!> input file. 
    43634372!------------------------------------------------------------------------------!
    4364     SUBROUTINE get_variable_string( id, variable_name, var_string, names_number)
     4373
     4374    SUBROUTINE get_variable_string( id, variable_name, var_string, names_number )
    43654375#if defined( __netcdf )
    43664376
     
    44284438#endif
    44294439    END SUBROUTINE get_variable_string
     4440
     4441
     4442!
     4443!------------------------------------------------------------------------------!
     4444! Description:
     4445! ------------
     4446!> Generalized routine for reading strings from a netCDF variable
     4447!> to replace existing get_variable_string ( )
     4448!>
     4449!> Improvements:
     4450!>   - Expanded string size limit from 25 to 512
     4451!>   - No longer removes spaces between text magically (this seems to have
     4452!>     been aimed at a very specific application, but I don't know what)
     4453!>   - Simplified implementation
     4454!>
     4455!> Caveats:
     4456!>   - Somehow I could not get the subroutine to work with str_array(:,:)
     4457!>     so I reverted to a hard-coded str_array(:,512), hopefully large enough
     4458!>     for most general applications.  This also means the character variable
     4459!>     used for str_array must be of size (:,512)
     4460!>     (ecc 20200128)   
     4461!------------------------------------------------------------------------------!
     4462
     4463 SUBROUTINE get_variable_string_generic ( id, var_name, str_array, num_str, str_len )
     4464
     4465    IMPLICIT NONE
     4466
     4467    CHARACTER(LEN=*),                INTENT(IN)    :: var_name       !> netCDF variable name
     4468    CHARACTER(LEN=512), ALLOCATABLE, INTENT(INOUT) :: str_array(:)   !> output string array
     4469
     4470    INTEGER(iwp)              :: buf_len   !> string buffer size
     4471    INTEGER(iwp)              :: id_var    !> netCDF variable ID
     4472    INTEGER(iwp)              :: k         !> generic counter
     4473
     4474    INTEGER(iwp), INTENT(IN)  :: id        !> netCDF file ID
     4475    INTEGER(iwp), INTENT(IN)  :: num_str   !> number of string elements in array
     4476    INTEGER(iwp), INTENT(IN)  :: str_len   !> size of each string element
     4477
     4478#if defined( __netcdf )
     4479
     4480!
     4481!-- set buffer length to up to hard-coded string size
     4482
     4483    buf_len = MIN( ABS(str_len), 512 )
     4484
     4485!
     4486!-- allocate necessary memories for string variables
     4487
     4488    ALLOCATE(str_array(num_str))
     4489!
     4490!-- get variable id
     4491
     4492    nc_stat = NF90_INQ_VARID( id, TRIM(var_name), id_var )
     4493!
     4494!-- extract string variables
     4495
     4496    DO k = 1, num_str
     4497       str_array(k) = ''
     4498       nc_stat = NF90_GET_VAR( id, id_var, str_array(k),  &
     4499                      start = (/ 1, k /), count = (/ buf_len, 1 /)  )
     4500       CALL handle_error ( 'get_variable_string_generic', 702 )
     4501    ENDDO
     4502
     4503#endif
     4504
     4505 END SUBROUTINE get_variable_string_generic
     4506
    44304507
    44314508!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.