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

Fixed domain extend check, readablity and documentation improvements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.