Changeset 4553 for palm/trunk/UTIL


Ignore:
Timestamp:
Jun 3, 2020 4:34:15 PM (4 years ago)
Author:
eckhard
Message:

Fixed domain extend check, readablity and documentation improvements

Location:
palm/trunk/UTIL/inifor/src
Files:
5 edited

Legend:

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

    r4538 r4553  
    2626! -----------------
    2727! $Id$
     28! Bumped version number
     29!
     30!
     31! 4538 2020-05-18 13:45:35Z eckhard
    2832! Bumped version number
    2933!
     
    192196    ACHAR( 10 ) // ' Copyright 2017-2020 Deutscher Wetterdienst Offenbach' !< Copyright notice
    193197 CHARACTER(LEN=*), PARAMETER ::  LOG_FILE_NAME = 'inifor.log' !< Name of INIFOR's log file
    194  CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.14'           !< INIFOR version number
     198 CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.15'           !< INIFOR version number
    195199 
    196200 END MODULE inifor_defs
  • palm/trunk/UTIL/inifor/src/inifor_grid.f90

    r4538 r4553  
    2626! -----------------
    2727! $Id$
     28! Fixed domain extent check
     29! Added and fixed code documentation
     30!
     31!
     32! 4538 2020-05-18 13:45:35Z eckhard
    2833! Modularize setup of PALM origin
    2934!
     
    687692    averaging_width_ns = averaging_angle * EARTH_RADIUS
    688693
    689     lonmin_tot = MIN(lam_centre - averaging_angle, lonmin_palm)
    690     lonmax_tot = MAX(lam_centre + averaging_angle, lonmax_palm)
    691     latmin_tot = MIN(phi_centre - averaging_angle, latmin_palm)
    692     latmax_tot = MAX(phi_centre + averaging_angle, latmax_palm)
    693 
    694     palm_domain_outside_cosmo = ANY(                                           &
    695        (/ lonmin_tot,   -lonmax_tot,   latmin_tot,   -latmax_tot/) .LT.        &
    696        (/ lonmin_cosmo, -lonmax_cosmo, latmin_cosmo, -latmax_cosmo/)           &
    697     )
    698 
    699     IF ( palm_domain_outside_cosmo )  THEN
    700        message = 'PALM domain or geostrophic averaging domains extend ' //     &
    701                  'outside COSMO domain.'
    702        CALL inifor_abort( 'setup_parameters', message )
    703     ENDIF
    704 
    705 
    706694!
    707695!-- Coriolis parameter
     
    10771065    latmax_palm = MAXVAL(palm_intermediate%clat)
    10781066
     1067    lonmin_tot = MIN(lam_centre - averaging_angle, lonmin_palm)
     1068    lonmax_tot = MAX(lam_centre + averaging_angle, lonmax_palm)
     1069    latmin_tot = MIN(phi_centre - averaging_angle, latmin_palm)
     1070    latmax_tot = MAX(phi_centre + averaging_angle, latmax_palm)
     1071
     1072    palm_domain_outside_cosmo = ANY(                                           &
     1073       (/ lonmin_tot,   -lonmax_tot,   latmin_tot,   -latmax_tot/) .LT.        &
     1074       (/ lonmin_cosmo, -lonmax_cosmo, latmin_cosmo, -latmax_cosmo/)           &
     1075    )
     1076
     1077    IF ( palm_domain_outside_cosmo )  THEN
     1078       message = 'PALM domain or geostrophic averaging domains extend ' //     &
     1079                 'outside COSMO domain.'
     1080       CALL inifor_abort( 'setup_grids', message )
     1081    ENDIF
     1082
     1083
    10791084    CALL init_averaging_grid(averaged_initial_scalar_profile, cosmo_grid,   &
    10801085            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
     
    12681273
    12691274    IF (setup_volumetric)  THEN
    1270        ALLOCATE( intermediate_grid%h(0:intermediate_grid%nx,            &
    1271                                      0:intermediate_grid%ny,            &
    1272                                      0:intermediate_grid%nz) )
    1273        intermediate_grid%h(:,:,:) = - EARTH_RADIUS
     1275       ALLOCATE( intermediate_grid%intermediate_h(0:intermediate_grid%nx,      &
     1276                                                  0:intermediate_grid%ny,      &
     1277                                                  0:intermediate_grid%nz) )
     1278       intermediate_grid%intermediate_h(:,:,:) = - EARTH_RADIUS
    12741279
    12751280!
    12761281!--    For w points, use hhl, for scalars use hfl
    12771282!--    compute the full heights for the intermediate grids
    1278        CALL interpolate_2d(cosmo_h, intermediate_grid%h, intermediate_grid)
     1283       CALL interpolate_2d(cosmo_h, intermediate_grid%intermediate_h, intermediate_grid)
    12791284       CALL find_vertical_neighbours_and_weights_interp(grid, intermediate_grid)
    12801285    ENDIF
     
    15501555!> kind : kind of quantity to be averaged using this averaging grid.
    15511556!>    Destinguishes COSMO-DE scalar and w-velocity levels. Note that finding the
    1552 !>    parent/COSMO columns for the region in get_cosmo_averaging_region() is
     1557!>    parent/COSMO columns for the region in get_latlon_averaging_region() is
    15531558!>    independent of 'kind' b/ecause INIFOR uses column-centred u and v velocity
    15541559!>    components, which are computed in the preprocessing step.
     
    15951600!-- Find and store COSMO columns that fall into the coordinate range
    15961601!-- given by avg_grid%clon, %clat
    1597     CALL get_cosmo_averaging_region(avg_grid, cosmo_grid)
     1602    CALL get_latlon_averaging_region(avg_grid, cosmo_grid)
    15981603
    15991604    ALLOCATE (avg_grid%kkk(avg_grid%n_columns, avg_grid%nz, 2) )
     
    16121617          message = "Averaging grid kind '" // TRIM(avg_grid%kind) // &
    16131618                    "' is not supported. Use 'scalar', 'u', or 'v'."
    1614           CALL inifor_abort('get_cosmo_averaging_region', message)
     1619          CALL inifor_abort('get_latlon_averaging_region', message)
    16151620
    16161621    END SELECT
    16171622
    16181623!
    1619 !-- For level-besed averaging, compute average heights
     1624!-- For level-based averaging, compute average heights
    16201625    level_based_averaging = ( TRIM(cfg%averaging_mode) == 'level' )
    16211626    IF (level_based_averaging)  THEN
    1622        ALLOCATE(avg_grid%h(1,1,SIZE(avg_grid%cosmo_h, 3)) )
     1627       ALLOCATE(avg_grid%intermediate_h(1,1,SIZE(avg_grid%cosmo_h, 3)) )
    16231628 
    1624        CALL average_2d(avg_grid%cosmo_h, avg_grid%h(1,1,:),             &
     1629       CALL average_2d(avg_grid%cosmo_h, avg_grid%intermediate_h(1,1,:),       &
    16251630                       avg_grid%iii, avg_grid%jjj)
    16261631
     
    16361641
    16371642
    1638  SUBROUTINE get_cosmo_averaging_region(avg_grid, cosmo_grid)
     1643!------------------------------------------------------------------------------!
     1644! Description:
     1645! ------------
     1646!> get_latlon_averaging_region() finds all mesocsale columns within the
     1647!> latitude-longitude reactagle given by the four values in avg_grid%lon(1:2)
     1648!> and %lat(1:2). The total number of all found columns is stored in
     1649!> avg_grid%n_columns, and their indices are stored in the sequential lists
     1650!> avg_grid%iii(:) and %jjj(:).
     1651!------------------------------------------------------------------------------!
     1652 SUBROUTINE get_latlon_averaging_region(avg_grid, cosmo_grid)
    16391653    TYPE(grid_definition), INTENT(INOUT)         ::  avg_grid
    16401654    TYPE(grid_definition), TARGET, INTENT(IN)    ::  cosmo_grid
     
    16631677          message = "Averaging grid kind '" // TRIM(avg_grid%kind) // &
    16641678                    "' is not supported. Use 'scalar', 'u', or 'v'."
    1665           CALL inifor_abort('get_cosmo_averaging_region', message)
     1679          CALL inifor_abort('get_latlon_averaging_region', message)
    16661680
    16671681    END SELECT
    16681682
    1669 !
    1670 !-- FIXME: make dlon, dlat parameters of the grid_defintion type
    16711683    dlon = cosmo_lon(1) - cosmo_lon(0)
    16721684    dlat = cosmo_lat(1) - cosmo_lat(0)
     
    16821694              " and " //                                                    &
    16831695              TRIM(str(jmin)) // " <= j <= " // TRIM(str(jmax))
    1684     CALL report( 'get_cosmo_averaging_region', message )
     1696    CALL report( 'get_latlon_averaging_region', message )
    16851697
    16861698    nx = imax - imin + 1
     
    17001712    ENDDO
    17011713
    1702  END SUBROUTINE get_cosmo_averaging_region
     1714 END SUBROUTINE get_latlon_averaging_region
    17031715
    17041716
  • palm/trunk/UTIL/inifor/src/inifor_io.f90

    r4538 r4553  
    2626! -----------------
    2727! $Id$
     28! Option --help now points the user to INIFOR's wiki page
     29! Remove deprecated command-line options -clon and -clat
     30!
     31!
     32! 4538 2020-05-18 13:45:35Z eckhard
    2833! Make setting the vertical PALM origin mandatory
    2934!
     
    444449    IF (arg_count .GT. 0)  THEN
    445450
    446        message = "The -clon and -clat command line options are depricated. " // &
    447           "Please remove them form your inifor command and specify the " // &
    448           "location of the PALM-4U origin either" // NEW_LINE(' ') // &
    449           "   - by setting the namelist parameters 'longitude' and 'latitude', or" // NEW_LINE(' ') // &
    450           "   - by providing a static driver netCDF file via the -static command-line option."
    451 
    452451       i = 1
    453452       DO  WHILE (i .LE. arg_count)
     
    487486                CALL get_option_argument( i, arg )
    488487                READ(arg, *) cfg%vg
    489 
    490              CASE( '-clon', '-clat' )
    491                 CALL inifor_abort('parse_command_line_arguments', message)
    492488
    493489             CASE( '-path', '-p', '--path' )
     
    560556                CALL print_version
    561557                PRINT *, ""
    562                 PRINT *, "For a list of command-line options have a look at the README file."
     558                PRINT *, &
     559                   "For documentation and a list of available command-line options " // NEW_LINE(" ") // &
     560                   " please visit https://palm.muk.uni-hannover.de/trac/wiki/doc/app/iofiles/inifor."
    563561                STOP
    564562
  • palm/trunk/UTIL/inifor/src/inifor_transform.f90

    r4523 r4553  
    2626! -----------------
    2727! $Id$
     28! Improved code readability and documentation
     29!
     30!
     31! 4523 2020-05-07 15:58:16Z eckhard
    2832! bugfix: pressure extrapolation
    2933! respect integer working precision (iwp) specified in inifor_defs.f90
     
    10371041       k_intermediate = 0
    10381042
    1039        column_base = palm_intermediate%h(i,j,0)
    1040        column_top  = palm_intermediate%h(i,j,nlev)
     1043       column_base = palm_intermediate%intermediate_h(i,j,0)
     1044       column_top  = palm_intermediate%intermediate_h(i,j,nlev)
    10411045
    10421046!
     
    10511055!--       current height within it
    10521056          current_height = palm_grid%z(k) + palm_grid%z0
    1053           h_top    = palm_intermediate%h(i,j,k_intermediate+1)
    1054           h_bottom = palm_intermediate%h(i,j,k_intermediate)
     1057          h_top    = palm_intermediate%intermediate_h(i,j,k_intermediate+1)
     1058          h_bottom = palm_intermediate%intermediate_h(i,j,k_intermediate)
    10551059
    10561060          point_is_above_grid = (current_height > column_top) !22000m, very unlikely
     
    10861090                k_intermediate = k_intermediate + 1
    10871091
    1088                 h_top    = palm_intermediate%h(i,j,k_intermediate+1)
    1089                 h_bottom = palm_intermediate%h(i,j,k_intermediate)
     1092                h_top    = palm_intermediate%intermediate_h(i,j,k_intermediate+1)
     1093                h_bottom = palm_intermediate%intermediate_h(i,j,k_intermediate)
    10901094                point_is_in_current_cell = (                                &
    10911095                   current_height >= h_bottom .AND.                         &
     
    11271131!> are adressed. While the _interp variant loops over all PALM grid columns
    11281132!> given by combinations of all index indices (i,j), this routine loops over a
    1129 !> subset of COSMO columns, which are sequantlially stored in the index lists
     1133!> subset of COSMO columns, which are sequentially stored in the index lists
    11301134!> iii(:) and jjj(:).
    11311135!------------------------------------------------------------------------------!
     
    11491153    nlev = SIZE(avg_grid%cosmo_h, 3)
    11501154
     1155!
     1156!-- For level-based averaging, use the profile of averaged vertical mesoscale
     1157!-- levels computed in init_averaging_grid().
    11511158    IF (level_based_averaging)  THEN
    1152        cosmo_h => avg_grid%h
     1159       cosmo_h => avg_grid%intermediate_h
    11531160    ELSE
    11541161       cosmo_h => avg_grid%cosmo_h
     
    11591166    DO  l = 1, avg_grid%n_columns
    11601167
     1168!--    The profile of averaged vertical mesoscale levels stored in
     1169!--    intermediate_h only contains one column. By using the same column -- and
     1170!--    consequently the same vertical interpolation neighbours and weights --
     1171!--   
    11611172       IF (level_based_averaging)  THEN
    11621173          i = 1
     
    11711182
    11721183!
    1173 !--    scan through avg_grid column until and set neighbour indices in
     1184!--    Scan through avg_grid column until and set neighbour indices in
    11741185!--    case current_height is either below column_base, in the current
    11751186!--    cell, or above column_top. Keep increasing current cell index until
    11761187!--    the current cell overlaps with the current_height.
    1177        k_intermediate = 1 !avg_grid%cosmo_h is indezed 1-based.
     1188       k_intermediate = 1 !avg_grid%cosmo_h is indexed 1-based.
    11781189       DO  k_palm = 1, avg_grid%nz
    11791190
  • palm/trunk/UTIL/inifor/src/inifor_types.f90

    r4538 r4553  
    2626! -----------------
    2727! $Id$
     28! Minor code readability improvements
     29!
     30!
     31! 4538 2020-05-18 13:45:35Z eckhard
    2832! Added boolean indicator for --static-driver option invocation
    2933!
     
    171175    REAL(wp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
    172176    REAL(wp), POINTER     ::  z(:)          !< coordinates of cell centers in z direction [m]
    173     REAL(wp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
     177    REAL(wp), ALLOCATABLE ::  intermediate_h(:,:,:) !< heights grid point for intermediate grids [m]
    174178    REAL(wp), POINTER     ::  cosmo_h(:,:,:)!< pointer to appropriate COSMO level heights (scalar/w) [m]
    175179    REAL(wp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
Note: See TracChangeset for help on using the changeset viewer.