Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/tests/test-input-files.f90

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
    23 !
     23! New test for negative start_hour and greater-than-one step_hour
     24!
    2425!
    2526! Former revisions:
     
    4445        ONLY :  PATH
    4546    USE grid,                                                                  &
    46         ONLY :  input_file_list
     47        ONLY :  get_input_file_list
    4748    USE test_utils
    4849   
    4950    IMPLICIT NONE
    5051
    51     CHARACTER(LEN=50)                              ::  title
     52    CHARACTER(LEN=60)                              ::  title
    5253    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  file_list, ref_list
    5354    LOGICAL                                        ::  res
    54     INTEGER                                        ::  i     
     55    INTEGER                                        ::  i
    5556
    5657    title = "input files - daylight saving to standard time"
     
    7071
    7172    ! Act
    72     CALL input_file_list(start_date_string='2017102823',                       &
    73                          start_hour=0, end_hour=5, step_hour=1,                &
    74                          path='./', prefix="laf", suffix='-test',              &
    75                          file_list=file_list)
     73    CALL get_input_file_list(start_date_string='2017102823',                   &
     74                             start_hour=0, end_hour=5, step_hour=1,            &
     75                             path='./', prefix="laf", suffix='-test',          &
     76                             file_list=file_list)
    7677
    7778    ! Assert
     
    9596
    9697    ! Act
    97     CALL input_file_list(start_date_string='2016022823',                       &
    98                          start_hour=0, end_hour=1, step_hour=1,                &
    99                          path='./', prefix="laf", suffix='-test',              &
    100                          file_list=file_list)
     98    CALL get_input_file_list(start_date_string='2016022823',                   &
     99                             start_hour=0, end_hour=1, step_hour=1,            &
     100                             path='./', prefix="laf", suffix='-test',          &
     101                             file_list=file_list)
     102
     103    ! Assert
     104    DO i = 1, 2
     105       res = res .AND. (TRIM(ref_list(i)) .EQ. TRIM(file_list(i)))
     106    END DO
     107
     108    DEALLOCATE( ref_list, file_list )
     109    CALL end_test(title, res)
     110
     111
     112
     113    title = "input files - negative start_hour and step_hour > 1 hour"
     114    CALL begin_test(title, res)
     115
     116    ! Arange
     117    ! ...a date range that inlcudes a leap day (29. Feb. 2016) which should be
     118    ! inlcuded in UTC time stamps.
     119    ALLOCATE( ref_list(4) )
     120    ref_list(1)  = './laf2017102823-test.nc'
     121    ref_list(2)  = './laf2017102901-test.nc'
     122    ref_list(3)  = './laf2017102903-test.nc'
     123    ref_list(4)  = './laf2017102904-test.nc'
     124
     125    ! Act
     126    CALL get_input_file_list(start_date_string='2017102901',                   &
     127                             start_hour=-2, end_hour=3, step_hour=2,           &
     128                             path='./', prefix="laf", suffix='-test',          &
     129                             file_list=file_list)
     130
     131    PRINT *, file_list
    101132
    102133    ! Assert
Note: See TracChangeset for help on using the changeset viewer.