Ignore:
Timestamp:
Dec 7, 2018 6:20:37 PM (5 years ago)
Author:
eckhard
Message:

inifor: Average initial profiles over the PALM, not the geostrophic, region

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

Legend:

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

    r3557 r3613  
    2626! -----------------
    2727! $Id$
     28! Moved version output to setup_parameters()
     29!
     30! 3557 2018-11-22 16:01:22Z eckhard
    2831! Updated documentation
    2932!
     
    121124!------------------------------------------------------------------------------
    122125 CALL run_control('init', 'void')
    123     CALL report('main_loop', 'Running INIFOR version ' // VERSION)
    124126
    125127!
  • palm/trunk/UTIL/inifor/src/inifor_defs.f90

    r3557 r3613  
    2626! -----------------
    2727! $Id$
     28! Bumped version number
     29!
     30!
     31! 3557 2018-11-22 16:01:22Z eckhard
    2832! Updated documentation
    2933!
     
    119123 INTEGER, PARAMETER          ::  FORCING_STEP = 1             !< Number of hours between forcing time steps [h]
    120124 REAL(dp), PARAMETER         ::  NUDGING_TAU = 21600.0_dp     !< Nudging relaxation time scale [s]
    121  CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.2'            !< INIFOR version number
     125 CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.3'            !< INIFOR version number
    122126 CHARACTER(LEN=*), PARAMETER ::  COPYRIGHT = 'Copyright 2017-2018 Leibniz Universitaet Hannover' // &
    123127     ACHAR( 10 ) // ' Copyright 2017-2018 Deutscher Wetterdienst Offenbach' !< Copyright notice
  • palm/trunk/UTIL/inifor/src/inifor_grid.f90

    r3557 r3613  
    2626! -----------------
    2727! $Id$
     28! Average initial profiles only over PALM domain region, not the
     29!     geostrophic-wind averaging region
     30! Fix unintended modification of COSMO heights
     31! Fix commenting out of setup_volumentric setting
     32! Moved version output to setup_parameters()
     33!
     34!
     35! 3557 2018-11-22 16:01:22Z eckhard
    2836! Updated documentation
    2937!
     
    150158    REAL(dp) ::  z_top             = 0.0_dp       !< height of the scalar top boundary [m]
    151159    REAL(dp) ::  zw_top            = 0.0_dp       !< height of the vertical velocity top boundary [m]
    152     REAL(dp) ::  lonmin            = 0.0_dp       !< Minimunm longitude of COSMO-DE's rotated-pole grid
    153     REAL(dp) ::  lonmax            = 0.0_dp       !< Maximum longitude of COSMO-DE's rotated-pole grid
    154     REAL(dp) ::  latmin            = 0.0_dp       !< Minimunm latitude of COSMO-DE's rotated-pole grid
    155     REAL(dp) ::  latmax            = 0.0_dp       !< Maximum latitude of COSMO-DE's rotated-pole grid
     160    REAL(dp) ::  lonmin_cosmo      = 0.0_dp       !< Minimunm longitude of COSMO-DE's rotated-pole grid [COSMO rotated-pole rad]
     161    REAL(dp) ::  lonmax_cosmo      = 0.0_dp       !< Maximum longitude of COSMO-DE's rotated-pole grid [COSMO rotated-pole rad]
     162    REAL(dp) ::  latmin_cosmo      = 0.0_dp       !< Minimunm latitude of COSMO-DE's rotated-pole grid [COSMO rotated-pole rad]
     163    REAL(dp) ::  latmax_cosmo      = 0.0_dp       !< Maximum latitude of COSMO-DE's rotated-pole grid [COSMO rotated-pole rad]
     164    REAL(dp) ::  lonmin_palm       = 0.0_dp       !< Minimunm longitude of PALM grid [COSMO rotated-pole rad]
     165    REAL(dp) ::  lonmax_palm       = 0.0_dp       !< Maximum longitude of PALM grid [COSMO rotated-pole rad]
     166    REAL(dp) ::  latmin_palm       = 0.0_dp       !< Minimunm latitude of PALM grid [COSMO rotated-pole rad]
     167    REAL(dp) ::  latmax_palm       = 0.0_dp       !< Maximum latitude of PALM grid [COSMO rotated-pole rad]
    156168    REAL(dp) ::  latitude          = 0.0_dp       !< geographical latitude of the PALM-4U origin, from inipar namelist [deg]
    157169    REAL(dp) ::  longitude         = 0.0_dp       !< geographical longitude of the PALM-4U origin, from inipar namelist [deg]
     
    255267    TYPE(grid_definition), TARGET ::  w_south_intermediate            !< intermediate grid for southern w boundary condition
    256268    TYPE(grid_definition), TARGET ::  w_top_intermediate              !< intermediate grid for top w boundary condition
    257     TYPE(grid_definition), TARGET ::  north_averaged_scalar_profile   !< grid of the northern scalar averaging region
    258     TYPE(grid_definition), TARGET ::  south_averaged_scalar_profile   !< grid of the southern scalar averaging region
    259     TYPE(grid_definition), TARGET ::  west_averaged_scalar_profile    !< grid of the western scalar averaging region
    260     TYPE(grid_definition), TARGET ::  east_averaged_scalar_profile    !< grid of the eastern scalar averaging region
    261     TYPE(grid_definition), TARGET ::  averaged_scalar_profile         !< grid of the central scalar averaging region
    262     TYPE(grid_definition), TARGET ::  averaged_w_profile              !< grid of the central w-velocity averaging region
     269    TYPE(grid_definition), TARGET ::  north_averaged_scalar_profile   !< grid of the northern geostrophic scalar averaging region
     270    TYPE(grid_definition), TARGET ::  south_averaged_scalar_profile   !< grid of the southern geostrophic scalar averaging region
     271    TYPE(grid_definition), TARGET ::  west_averaged_scalar_profile    !< grid of the western geostrophic scalar averaging region
     272    TYPE(grid_definition), TARGET ::  east_averaged_scalar_profile    !< grid of the eastern geostrophic scalar averaging region
     273    TYPE(grid_definition), TARGET ::  averaged_scalar_profile         !< grid of the central geostrophic scalar averaging region
     274    TYPE(grid_definition), TARGET ::  averaged_w_profile              !< grid of the central geostrophic w-velocity averaging region
     275    TYPE(grid_definition), TARGET ::  averaged_initial_scalar_profile !< averaging grid for initial scalar profiles
     276    TYPE(grid_definition), TARGET ::  averaged_initial_w_profile      !< averaging grid for the initial w profile
    263277
    264278    TYPE(io_group), ALLOCATABLE, TARGET ::  io_group_list(:)  !< List of I/O groups, which group together output variables that share the same input variable
     
    406420       CALL validate_config( cfg )
    407421
     422       CALL report('main_loop', 'Running INIFOR version ' // VERSION)
    408423       CALL report('setup_parameters', "initialization mode: " // TRIM(cfg % ic_mode))
    409424       CALL report('setup_parameters', "       forcing mode: " // TRIM(cfg % bc_mode))
     
    501516       ndepths = SIZE(depths)
    502517
    503        lonmin = MINVAL(rlon) * TO_RADIANS
    504        lonmax = MAXVAL(rlon) * TO_RADIANS
    505        latmin = MINVAL(rlat) * TO_RADIANS
    506        latmax = MAXVAL(rlat) * TO_RADIANS
     518       lonmin_cosmo = MINVAL(rlon) * TO_RADIANS
     519       lonmax_cosmo = MAXVAL(rlon) * TO_RADIANS
     520       latmin_cosmo = MINVAL(rlat) * TO_RADIANS
     521       latmax_cosmo = MAXVAL(rlat) * TO_RADIANS
    507522 CALL run_control('time', 'comp')
    508523
     
    691706               xmin=0.0_dp, xmax=lx,                                           &
    692707               ymin=0.0_dp, ymax=ly,                                           &
    693                x0=x0, y0=y0, z0=z0,                      &
     708               x0=x0, y0=y0, z0=z0,                                            &
    694709               nx=nx, ny=ny, nz=nz, z=z, zw=zw, ic_mode=cfg % ic_mode)
    695710
     
    697712!--    Subtracting 1 because arrays will be allocated with nlon + 1 elements.
    698713       CALL init_grid_definition('cosmo-de', grid=cosmo_grid,                  &
    699                xmin=lonmin, xmax=lonmax,                                       &
    700                ymin=latmin, ymax=latmax,                                       &
    701                x0=x0, y0=y0, z0=0.0_dp,             &
     714               xmin=lonmin_cosmo, xmax=lonmax_cosmo,                           &
     715               ymin=latmin_cosmo, ymax=latmax_cosmo,                           &
     716               x0=x0, y0=y0, z0=0.0_dp,                                        &
    702717               nx=nlon-1, ny=nlat-1, nz=nlev-1)
    703718
     
    710725               xmin=0.0_dp, xmax=lx,                                           &
    711726               ymin=0.0_dp, ymax=ly,                                           &
    712                x0=x0, y0=y0, z0=z0,                      &
     727               x0=x0, y0=y0, z0=z0,                                            &
    713728               nx=nx, ny=ny, nz=nlev-2)
    714729
     
    10021017! Section 3: Define profile grids
    10031018!------------------------------------------------------------------------------
     1019
     1020       lonmin_palm = MINVAL(palm_intermediate % clon)
     1021       lonmax_palm = MAXVAL(palm_intermediate % clon)
     1022       latmin_palm = MINVAL(palm_intermediate % clat)
     1023       latmax_palm = MAXVAL(palm_intermediate % clat)
     1024
     1025       CALL init_averaging_grid(averaged_initial_scalar_profile, cosmo_grid,   &
     1026               x = 0.5_dp * lx, y = 0.5_dp * ly, z = z, z0 = z0,               &
     1027               lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
     1028               latmin = latmin_palm, latmax = latmax_palm,                     &
     1029               kind='scalar')
     1030
     1031       CALL init_averaging_grid(averaged_initial_w_profile, cosmo_grid,        &
     1032               x = 0.5_dp * lx, y = 0.5_dp * ly, z = zw, z0 = z0,              &
     1033               lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
     1034               latmin = latmin_palm, latmax = latmax_palm,                     &
     1035               kind='w')
    10041036
    10051037       CALL init_averaging_grid(averaged_scalar_profile, cosmo_grid,           &
     
    11761208!--    domain volume. Instead we need vertical weights for the intermediate
    11771209!--    profile grids, which get computed in setup_averaging().
    1178 !--    setup_volumetric = .TRUE.
     1210       setup_volumetric = .TRUE.
    11791211       IF (PRESENT(ic_mode))  THEN
    11801212          IF (TRIM(ic_mode) == 'profile')  setup_volumetric = .FALSE.
     
    14471479! Description:
    14481480! ------------
    1449 !> Initializes averagin_grid-type variables.
     1481!> Initializes averaging grids
    14501482!>
    14511483!> Input parameters:
     
    14701502!> Output parameters:
    14711503!> ------------------
    1472 !> avg_grid : averaging_grid variable to be initialized.
     1504!> avg_grid : averagin grid to be initialized
    14731505!------------------------------------------------------------------------------!
    14741506    SUBROUTINE init_averaging_grid(avg_grid, cosmo_grid, x, y, z, z0,          &
     
    14791511       REAL(dp), INTENT(IN)                 ::  x, y, z0
    14801512       REAL(dp), INTENT(IN), TARGET         ::  z(:)
    1481        REAL(dp), INTENT(IN)                 ::  lonmin, lonmax, latmin, latmax
     1513       REAL(dp), INTENT(IN)                 ::  lonmin !< lower longitude bound of the averaging grid region [COSMO rotated-pole rad]
     1514       REAL(dp), INTENT(IN)                 ::  lonmax !< upper longitude bound of the averaging grid region [COSMO rotated-pole rad]
     1515       REAL(dp), INTENT(IN)                 ::  latmin !< lower latitude bound of the averaging grid region [COSMO rotated-pole rad]
     1516       REAL(dp), INTENT(IN)                 ::  latmax !< lower latitude bound of the averaging grid region [COSMO rotated-pole rad]
    14821517
    14831518       CHARACTER(LEN=*), INTENT(IN)         ::  kind
     
    15291564!
    15301565!--    For level-besed averaging, compute average heights
    1531        level_based_averaging = .TRUE.
     1566       level_based_averaging = ( TRIM(cfg % averaging_mode) == 'level' )
    15321567       IF (level_based_averaging)  THEN
    15331568          ALLOCATE(avg_grid % h(1,1,SIZE(avg_grid % cosmo_h, 3)) )
    15341569 
    1535           CALL average_2d(avg_grid % cosmo_h, avg_grid % h(1,1,:),                            &
     1570          CALL average_2d(avg_grid % cosmo_h, avg_grid % h(1,1,:),             &
    15361571                          avg_grid % iii, avg_grid % jjj)
    15371572       END IF
    15381573
    15391574!
    1540 !--    Copy averaged grid to all COSMO columns, leads to computing the same
    1541 !--    vertical interpolation weights for all columns and to COSMO grid level
    1542 !--    based averaging onto the averaged COSMO heights.
    1543        IF ( TRIM(cfg % averaging_mode) == 'level' )  THEN
    1544           FORALL(                                                              &
    1545              i=1:SIZE(avg_grid % cosmo_h, 1),                                  &
    1546              j=1:SIZE(avg_grid % cosmo_h, 2)                                   &
    1547           )   avg_grid % cosmo_h(i,j,:) = avg_grid % h(1,1,:)
    1548        END IF
    1549 
    1550 !
    15511575!--    Compute vertical weights and neighbours
    1552        CALL find_vertical_neighbours_and_weights_average(avg_grid)
     1576       CALL find_vertical_neighbours_and_weights_average(                      &
     1577          avg_grid, level_based_averaging                                      &
     1578       )
    15531579
    15541580    END SUBROUTINE init_averaging_grid
     
    24332459       )
    24342460       IF (TRIM(ic_mode) == 'profile')  THEN
    2435           output_var_table(3) % averaging_grid => averaged_scalar_profile
     2461          output_var_table(3) % averaging_grid => averaged_initial_scalar_profile
    24362462       END IF
    24372463
     
    25092535       )
    25102536       IF (TRIM(ic_mode) == 'profile')  THEN
    2511           output_var_table(9) % averaging_grid => averaged_scalar_profile
     2537          output_var_table(9) % averaging_grid => averaged_initial_scalar_profile
    25122538       END IF
    25132539
     
    25852611       )
    25862612       IF (TRIM(ic_mode) == 'profile')  THEN
    2587           output_var_table(15) % averaging_grid => averaged_scalar_profile
     2613          output_var_table(15) % averaging_grid => averaged_initial_scalar_profile
    25882614       END IF
    25892615
     
    26612687       )
    26622688       IF (TRIM(ic_mode) == 'profile')  THEN
    2663           output_var_table(21) % averaging_grid => averaged_scalar_profile
     2689          output_var_table(21) % averaging_grid => averaged_initial_scalar_profile
    26642690       END IF
    26652691
     
    27372763       )
    27382764       IF (TRIM(ic_mode) == 'profile')  THEN
    2739           output_var_table(27) % averaging_grid => averaged_w_profile
     2765          output_var_table(27) % averaging_grid => averaged_initial_w_profile
    27402766       END IF
    27412767
  • palm/trunk/UTIL/inifor/src/inifor_transform.f90

    r3557 r3613  
    2626! -----------------
    2727! $Id$
     28! Use averaged heights profile for level-based averaging instead of modified
     29!    COSMO heights array
     30!
     31!
     32! 3557 2018-11-22 16:01:22Z eckhard
    2833! Updated documentation
    2934!
     
    898903!> iii(:) and jjj(:).
    899904!------------------------------------------------------------------------------!
    900     SUBROUTINE find_vertical_neighbours_and_weights_average( avg_grid )
    901        TYPE(grid_definition), INTENT(INOUT) ::  avg_grid
    902 
    903        INTEGER  ::  i, j, k_palm, k_intermediate, l, nlev
    904        LOGICAL  ::  point_is_below_grid, point_is_above_grid,                  &
    905                     point_is_in_current_cell
    906        REAL(dp) ::  current_height, column_base, column_top, h_top, h_bottom,  &
    907                     weight
     905    SUBROUTINE find_vertical_neighbours_and_weights_average(                   &
     906       avg_grid, level_based_averaging                                         &
     907    )
     908
     909       TYPE(grid_definition), INTENT(INOUT), TARGET ::  avg_grid
     910       LOGICAL                                      ::  level_based_averaging
     911
     912       INTEGER           ::  i, j, k_palm, k_intermediate, l, nlev
     913       LOGICAL           ::  point_is_below_grid, point_is_above_grid,         &
     914                             point_is_in_current_cell
     915       REAL(dp)          ::  current_height, column_base, column_top, h_top,   &
     916                             h_bottom, weight
     917       REAL(dp), POINTER ::  cosmo_h(:,:,:)
    908918
    909919
     
    911921
    912922       nlev = SIZE(avg_grid % cosmo_h, 3)
     923
     924       IF (level_based_averaging)  THEN
     925          cosmo_h => avg_grid % h
     926       ELSE
     927          cosmo_h => avg_grid % cosmo_h
     928       END IF
    913929
    914930!
     
    916932       DO l = 1, avg_grid % n_columns
    917933
    918           i = avg_grid % iii(l)
    919           j = avg_grid % jjj(l)
    920 
    921           column_base = avg_grid % cosmo_h(i,j,1)
    922           column_top  = avg_grid % cosmo_h(i,j,nlev)
     934          IF (level_based_averaging)  THEN
     935             i = 1
     936             j = 1
     937          ELSE
     938             i = avg_grid % iii(l)
     939             j = avg_grid % jjj(l)
     940          END IF
     941
     942          column_base = cosmo_h(i,j,1)
     943          column_top  = cosmo_h(i,j,nlev)
    923944
    924945!
     
    934955!--          current height within it
    935956             current_height = avg_grid % z(k_palm) + avg_grid % z0
    936              h_top    = avg_grid % cosmo_h(i,j,k_intermediate+1)
    937              h_bottom = avg_grid % cosmo_h(i,j,k_intermediate)
     957             h_top    = cosmo_h(i,j,k_intermediate+1)
     958             h_bottom = cosmo_h(i,j,k_intermediate)
    938959
    939960!
     
    972993                   k_intermediate = k_intermediate + 1
    973994
    974                    h_top    = avg_grid % cosmo_h(i,j,k_intermediate+1)
    975                    h_bottom = avg_grid % cosmo_h(i,j,k_intermediate)
     995                   h_top    = cosmo_h(i,j,k_intermediate+1)
     996                   h_bottom = cosmo_h(i,j,k_intermediate)
    976997                   point_is_in_current_cell = (                                &
    977998                      current_height >= h_bottom .AND.                         &
Note: See TracChangeset for help on using the changeset viewer.