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

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Improved real-to-string conversion
    2324!
    2425!
     
    4344        ONLY :  C_CHAR, C_INT, C_PTR, C_SIZE_T
    4445    USE defs,                                                                  &
    45         ONLY :  dp, PI, DATE
     46        ONLY :  dp, PI, DATE, SNAME
    4647
    4748    IMPLICIT NONE
     
    279280    ! Convert a real number to a string in scientific notation
    280281    ! showing four significant digits.
    281     CHARACTER(LEN=11) FUNCTION real_to_str(val, format)
     282    CHARACTER(LEN=SNAME) FUNCTION real_to_str(val, format)
    282283
    283284        REAL(dp), INTENT(IN)                   ::  val
     
    285286
    286287        IF (PRESENT(format))  THEN
    287            WRITE(real_to_str, TRIM(format)) val
     288           WRITE(real_to_str, format) val
    288289        ELSE
    289290           WRITE(real_to_str, '(E11.4)') val
    290            real_to_str = ADJUSTL(real_to_str)
    291291        END IF
     292        real_to_str = ADJUSTL(real_to_str)
    292293
    293294    END FUNCTION real_to_str
Note: See TracChangeset for help on using the changeset viewer.