Ignore:
Timestamp:
Feb 5, 2019 5:02:38 PM (5 years ago)
Author:
eckhard
Message:

inifor: bugfix: removed dependency on soilmoisture input files; added netcdf preprocessor flag

File:
1 edited

Legend:

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

    r3680 r3716  
    2626! -----------------
    2727! $Id$
     28! Removed dependency on soilmoisture input files
     29!
     30!
     31! 3680 2019-01-18 14:54:12Z knoop
    2832! Moved get_input_file_list() here from grid module, added check for presence of
    2933!    input files
     
    576580   SUBROUTINE get_input_file_list( start_date_string, start_hour, end_hour,    &
    577581                                   step_hour, input_path, prefix, suffix,      &
    578                                    file_list )
     582                                   file_list, nocheck )
    579583
    580584      CHARACTER (LEN=DATE), INTENT(IN) ::  start_date_string
     
    582586      INTEGER,              INTENT(IN) ::  start_hour, end_hour, step_hour
    583587      CHARACTER(LEN=*), ALLOCATABLE, INTENT(INOUT) ::  file_list(:)
     588      LOGICAL, OPTIONAL, INTENT(IN)    ::  nocheck
    584589
    585590      INTEGER             ::  number_of_intervals, hour, i
    586591      CHARACTER(LEN=DATE) ::  date_string
    587592      CHARACTER(LEN=PATH) ::  file_name
     593      LOGICAL             ::  check_files
    588594
    589595      CALL get_datetime_file_list( start_date_string, start_hour, end_hour,    &
     
    591597                                   file_list )
    592598
    593       tip = "Please check if you specified the correct file prefix " //        &
    594             "using the options --input-prefix, --flow-prefix, etc."
    595 
    596       DO i = 1, SIZE(file_list)
    597           CALL verify_file(file_list(i), 'input', tip)
    598       END DO
     599      check_files = .TRUE.
     600      IF ( PRESENT ( nocheck ) )  THEN
     601         IF ( nocheck )  check_files = .FALSE.
     602      END IF
     603
     604      IF ( check_files )  THEN
     605
     606         tip = "Please check if you specified the correct file prefix " //     &
     607               "using the options --input-prefix, --flow-prefix, etc."
     608
     609         DO i = 1, SIZE(file_list)
     610             CALL verify_file(file_list(i), 'input', tip)
     611         END DO
     612
     613      END IF
    599614
    600615   END SUBROUTINE get_input_file_list
Note: See TracChangeset for help on using the changeset viewer.