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/util.f90

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Expose error measure as parameter in assert_equal()
    2324!
    2425!
     
    7475    END SUBROUTINE end_test
    7576
    76     LOGICAL FUNCTION assert_equal(a, b, msg)
     77    LOGICAL FUNCTION assert_equal(a, b, msg, ratio)
     78       REAL, OPTIONAL, INTENT(IN)     ::  ratio
    7779       REAL, DIMENSION(:), INTENT(IN) ::  a, b
    78        CHARACTER(LEN=*), INTENT(IN)   :: msg
     80       CHARACTER(LEN=*), INTENT(IN)   ::  msg
    7981
    80        assert_equal = assert(a, b, 'eq')
     82       IF ( PRESENT(ratio) )  THEN
     83           assert_equal = assert(a, b, 'eq', ratio)
     84       ELSE
     85           assert_equal = assert(a, b, 'eq')
     86       END IF
     87
    8188       IF (assert_equal .eqv. .TRUE.)  THEN
    8289           PRINT *, "Equality assertion for ", msg, " was successful."
     
    8895    END FUNCTION assert_equal
    8996
    90     LOGICAL FUNCTION assert(a, b, mode, eps)
     97    LOGICAL FUNCTION assert(a, b, mode, ratio)
    9198
    9299       REAL, DIMENSION(:), INTENT(IN) ::  a, b
    93        REAL, OPTIONAL, INTENT(IN)     ::  eps
     100       REAL, OPTIONAL, INTENT(IN)     ::  ratio
    94101       CHARACTER(LEN=*), INTENT(IN)   ::  mode
    95102
     
    98105
    99106       max_rel_diff = 10 * EPSILON(1.0)
    100        IF (PRESENT(eps)) max_rel_diff = eps
     107       IF (PRESENT(ratio)) max_rel_diff = ratio
    101108
    102109       SELECT CASE( TRIM(mode) )
Note: See TracChangeset for help on using the changeset viewer.