Ignore:
Timestamp:
May 18, 2020 1:45:35 PM (4 years ago)
Author:
eckhard
Message:

inifor: Fix issue where --elevation/-z option was ignored, make it mandatory

File:
1 edited

Legend:

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

    r4523 r4538  
    2626! -----------------
    2727! $Id$
     28! Make setting the vertical PALM origin mandatory
     29!
     30!
     31! 4523 2020-05-07 15:58:16Z eckhard
    2832! respect integer working precision (iwp) specified in inifor_defs.f90
    2933!
     
    139143               NC_DEPTH_NAME, NC_HHL_NAME, NC_RLAT_NAME, NC_RLON_NAME,         &
    140144               NC_ROTATED_POLE_NAME, NC_POLE_LATITUDE_NAME,                    &
    141                NC_POLE_LONGITUDE_NAME, RHO_L, iwp, wp
     145               NC_POLE_LONGITUDE_NAME, RHO_L, iwp, wp,                         &
     146               PIDS_ORIGIN_LON, PIDS_ORIGIN_LAT, PIDS_ORIGIN_Z
    142147    USE inifor_types
    143148    USE inifor_util,                                                           &
     
    431436    cfg%soil_prefix_is_set = .FALSE.
    432437    cfg%soilmoisture_prefix_is_set = .FALSE.
     438    cfg%static_driver_is_set = .FALSE.
    433439    cfg%ug_defined_by_user = .FALSE.
    434440    cfg%vg_defined_by_user = .FALSE.
     
    503509
    504510             CASE( '-static', '-t', '--static-driver' )
     511                cfg%static_driver_is_set = .TRUE.
    505512                CALL get_option_argument( i, arg )
    506513                cfg%static_driver_file = TRIM(arg)
     
    762769       message = "You specified only one component of the geostrophic " // &
    763770                 "wind. Please specify either both or none."
     771       CALL inifor_abort( 'validate_config', message )
     772    ENDIF
     773
     774    IF ( .NOT. cfg%static_driver_is_set .AND. .NOT. cfg%z0_is_set )  THEN
     775       message =                                                               &
     776          "The vertical origin of the PALM grid has not been defined. " // NEW_LINE(" ") // &
     777          "Please specify the right value for your setup by either " // NEW_LINE(" ") // &
     778          "  - using the command-line option --elevation <height above sea level>, or by" // NEW_LINE(" ") // &
     779          "  - specifying a static driver file using --static <filename> in order to use " // NEW_LINE(" ") // &
     780          "    use the value of origin_z (and origin_lon and origin_lat) specifed therein."
    764781       CALL inifor_abort( 'validate_config', message )
    765782    ENDIF
     
    15121529 END SUBROUTINE check
    15131530
     1531
     1532!------------------------------------------------------------------------------!
     1533! Description:
     1534! ------------
     1535!> Setup the origin of the PALM coordinate system based on what is given in the
     1536!> INIFOR namelist file and via an optional static driver.
     1537!------------------------------------------------------------------------------!
     1538 SUBROUTINE set_palm_origin( cfg, namelist_longitude, namelist_latitude,       &
     1539                             origin_lon, origin_lat, z0 )
     1540
     1541    TYPE(inifor_config), INTENT(IN) ::  cfg
     1542    REAL(wp), INTENT(IN)            ::  namelist_longitude, namelist_latitude
     1543    REAL(wp), INTENT(OUT)           ::  origin_lon, origin_lat, z0
     1544
     1545    message = 'Reading PALM-4U origin from'
     1546    IF ( TRIM( cfg%static_driver_file ) .NE. '' )  THEN
     1547
     1548       origin_lon = get_netcdf_attribute( cfg%static_driver_file, TRIM( PIDS_ORIGIN_LON ) )
     1549       origin_lat = get_netcdf_attribute( cfg%static_driver_file, TRIM( PIDS_ORIGIN_LAT ) )
     1550       z0         = get_netcdf_attribute( cfg%static_driver_file, TRIM( PIDS_ORIGIN_Z ) )
     1551
     1552       message = TRIM(message) // " static driver file '"                      &
     1553                               // TRIM( cfg%static_driver_file ) // "'"
     1554
     1555
     1556    ELSE
     1557
     1558       origin_lon = namelist_longitude
     1559       origin_lat = namelist_latitude
     1560
     1561       message = TRIM( message ) // " namlist file '"                          &
     1562                                 // TRIM( cfg%namelist_file ) // "'"
     1563
     1564    ENDIF
     1565    origin_lon = origin_lon * TO_RADIANS
     1566    origin_lat = origin_lat * TO_RADIANS
     1567
     1568    CALL report('set_palm_origin', message)
     1569
     1570    IF ( cfg%z0_is_set )  THEN
     1571       z0 = cfg%z0
     1572       IF ( TRIM( cfg%static_driver_file ) .NE. '' )  THEN
     1573          message = 'You specified both --static-driver/-t and --elevation/-z0. ' // &
     1574                    'Using the command line value (' // TRIM( real_to_str_f( cfg%z0 ) ) // &
     1575                    ') instead of static driver value (' // TRIM( real_to_str_f( z0 ) ) // ').'
     1576          CALL warn( 'set_palm_origin', message )
     1577       ENDIF
     1578    ENDIF
     1579
     1580 END SUBROUTINE set_palm_origin
     1581
    15141582 END MODULE inifor_io
    15151583#endif
Note: See TracChangeset for help on using the changeset viewer.