Ignore:
Timestamp:
Jan 17, 2019 2:12:17 PM (5 years ago)
Author:
eckhard
Message:

inifor: bugfix: avoid empty averaging regions, check if all input files are present

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/inifor_grid.f90

    r3618 r3678  
    2626! -----------------
    2727! $Id$
     28! bugfix: Avoid empty averaging regions for small PALM domains
     29! change: moved get_input_file_list() to io module
     30!
     31!
     32! 3618 2018-12-10 13:25:22Z eckhard
    2833! Prefixed all INIFOR modules with inifor_, removed unused variables
    2934!
     
    112117        ONLY:  get_netcdf_attribute, get_netcdf_dim_vector,                    &
    113118               get_netcdf_variable, parse_command_line_arguments,              &
    114                validate_config
     119               get_input_file_list, validate_config
    115120    USE inifor_transform,                                                      &
    116121        ONLY:  average_2d, rotate_to_cosmo, find_horizontal_neighbours,&
     
    16251630       dlat = cosmo_lat(1) - cosmo_lat(0)
    16261631
    1627        imin = CEILING( (avg_grid % lon(1) - cosmo_lon(0)) / dlon )
    1628        imax = FLOOR  ( (avg_grid % lon(2) - cosmo_lon(0)) / dlon )
    1629 
    1630        jmin = CEILING( (avg_grid % lat(1) - cosmo_lat(0)) / dlat )
    1631        jmax = FLOOR  ( (avg_grid % lat(2) - cosmo_lat(0)) / dlat )
     1632       imin = FLOOR  ( (avg_grid % lon(1) - cosmo_lon(0)) / dlon )
     1633       imax = CEILING( (avg_grid % lon(2) - cosmo_lon(0)) / dlon )
     1634
     1635       jmin = FLOOR  ( (avg_grid % lat(1) - cosmo_lat(0)) / dlat )
     1636       jmax = CEILING( (avg_grid % lat(2) - cosmo_lat(0)) / dlat )
    16321637       
    16331638       message = "Averaging '" // TRIM(avg_grid % kind) // "' over "//         &
     
    36413646
    36423647
    3643     SUBROUTINE get_input_file_list(start_date_string, start_hour, end_hour,        &
    3644                                    step_hour, path, prefix, suffix, file_list)
    3645 
    3646        CHARACTER (LEN=DATE), INTENT(IN) ::  start_date_string
    3647        CHARACTER (LEN=*),    INTENT(IN) ::  prefix, suffix, path
    3648        INTEGER,              INTENT(IN) ::  start_hour, end_hour, step_hour
    3649        CHARACTER(LEN=*), ALLOCATABLE, INTENT(INOUT) ::  file_list(:)
    3650 
    3651        INTEGER             ::  number_of_intervals, hour, i
    3652        CHARACTER(LEN=DATE) ::  date_string
    3653 
    3654        number_of_intervals = CEILING( REAL(end_hour - start_hour) / step_hour )
    3655        ALLOCATE( file_list(number_of_intervals + 1) )
    3656 
    3657        DO i = 0, number_of_intervals
    3658           hour = start_hour + i * step_hour
    3659           date_string = add_hours_to(start_date_string, hour)
    3660 
    3661           file_list(i+1) = TRIM(path) // TRIM(prefix) // TRIM(date_string) //    &
    3662                            TRIM(suffix) // '.nc'
    3663           message = "Set up input file name '" // TRIM(file_list(i+1)) //"'"
    3664           CALL report('input_file_list', message)
    3665        END DO
    3666 
    3667     END SUBROUTINE get_input_file_list
    3668 
    3669 
    36703648!------------------------------------------------------------------------------!
    36713649! Description:
Note: See TracChangeset for help on using the changeset viewer.