Ignore:
Timestamp:
Sep 11, 2020 10:00:26 AM (4 years ago)
Author:
eckhard
Message:

Support for homogeneous (domain-averaged) boundary conditions and soil profile initialization

File:
1 edited

Legend:

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

    r4659 r4675  
    2626! -----------------
    2727! $Id$
     28! Support for profile initialization of soil and for homogeneous (profile)
     29!    boundary conditions, including respective command-line options
     30! Improved code formatting
     31!
     32!
     33! 4659 2020-08-31 11:21:17Z eckhard
    2834! Only define netCDF variables in enabled IO groups
    2935! Added cloud and precipitation quantiteis (cloud water, cloud ice, rain, snow
     
    181187    USE inifor_control
    182188    USE inifor_defs,                                                           &
    183         ONLY:  DATE, EARTH_RADIUS, TO_RADIANS, TO_DEGREES, PI,                 &
     189        ONLY:  CFG_INIT_PROFILE, CFG_INIT_SOIL_VOLUME, CFG_INIT_SOIL_PROFILE,  &
     190               CFG_FORCING_HETERO, CFG_FORCING_HOMO, CFG_FORCING_NUDGING,      &
     191               DATE, EARTH_RADIUS, TO_RADIANS, TO_DEGREES, PI,                 &
    184192               SNAME, LNAME, PATH, FORCING_STEP, FILL_ITERATIONS,              &
    185193               BETA, P_SL, T_SL, BETA, RD, RV, G, P_REF, RD_PALM, CP_PALM,     &
     
    297305    INTEGER(iwp) ::  ndepths !< number of COSMO-DE soil layers
    298306    INTEGER(iwp) ::  start_hour_flow          !< start of flow forcing in number of hours relative to start_date
    299     INTEGER(iwp) ::  start_hour_soil          !< start of soil forcing in number of hours relative to start_date, typically equals start_hour_flow
    300307    INTEGER(iwp) ::  start_hour_radiation     !< start of radiation forcing in number of hours relative to start_date, 0 to 2 hours before start_hour_flow to reconstruct hourly averages from one- to three hourly averages of the input data
    301308    INTEGER(iwp) ::  start_hour_precipitation !< start of forcing for precipitaiton forcing in number of hours relative to start_date
     
    362369    TYPE(grid_definition), TARGET ::  w_south_intermediate            !< intermediate grid for southern w boundary condition
    363370    TYPE(grid_definition), TARGET ::  w_top_intermediate              !< intermediate grid for top w boundary condition
    364     TYPE(grid_definition), TARGET ::  north_averaged_scalar_profile   !< grid of the northern geostrophic scalar averaging region
    365     TYPE(grid_definition), TARGET ::  south_averaged_scalar_profile   !< grid of the southern geostrophic scalar averaging region
    366     TYPE(grid_definition), TARGET ::  west_averaged_scalar_profile    !< grid of the western geostrophic scalar averaging region
    367     TYPE(grid_definition), TARGET ::  east_averaged_scalar_profile    !< grid of the eastern geostrophic scalar averaging region
    368     TYPE(grid_definition), TARGET ::  averaged_scalar_profile         !< grid of the central geostrophic scalar averaging region
    369     TYPE(grid_definition), TARGET ::  averaged_w_profile              !< grid of the central geostrophic w-velocity averaging region
    370     TYPE(grid_definition), TARGET ::  averaged_initial_scalar_profile !< averaging grid for initial scalar profiles
    371     TYPE(grid_definition), TARGET ::  averaged_initial_w_profile      !< averaging grid for the initial w profile
     371    TYPE(grid_definition), TARGET ::  north_geostrophic_scalar_profile!< grid of the northern geostrophic scalar averaging region
     372    TYPE(grid_definition), TARGET ::  south_geostrophic_scalar_profile!< grid of the southern geostrophic scalar averaging region
     373    TYPE(grid_definition), TARGET ::  west_geostrophic_scalar_profile !< grid of the western geostrophic scalar averaging region
     374    TYPE(grid_definition), TARGET ::  east_geostrophic_scalar_profile !< grid of the eastern geostrophic scalar averaging region
     375    TYPE(grid_definition), TARGET ::  geostrophic_scalar_profile      !< grid of the central geostrophic scalar averaging region
     376    TYPE(grid_definition), TARGET ::  geostrophic_w_profile           !< grid of the central geostrophic w-velocity averaging region
     377    TYPE(grid_definition), TARGET ::  averaged_soil_profile           !< averaging grid for initial soil profiles
     378    TYPE(grid_definition), TARGET ::  averaged_scalar_profile         !< averaging grid for initial and boundary condition scalar profiles
     379    TYPE(grid_definition), TARGET ::  averaged_w_profile              !< averaging grid for initial and boundary condition scalar profiles
     380    TYPE(grid_definition), TARGET ::  averaged_scalar_top_point       !< averaging grid for top scalar boundary conditions for homogeneous forcing mode
     381    TYPE(grid_definition), TARGET ::  averaged_w_top_point            !< averaging grid for top w boundary condition for homogeneous forcing mode
    372382
    373383    TYPE(io_group), ALLOCATABLE, TARGET ::  io_group_list(:)  !< List of I/O groups, which group together output variables that share the same input variable
     
    432442!-- Parameters for file names
    433443    start_hour_flow = 0
    434     start_hour_soil = 0
    435444    start_hour_radiation = 0
    436445    start_hour_precipitation = start_hour_flow
     
    464473    cfg%static_driver_file = ''
    465474    cfg%output_file = './palm-4u-input.nc'
    466     cfg%ic_mode = 'profile'
    467     cfg%bc_mode = 'real'
     475    cfg%ic_mode = CFG_INIT_PROFILE
     476    cfg%isc_mode = CFG_INIT_SOIL_VOLUME
     477    cfg%bc_mode = CFG_FORCING_HETERO
    468478    cfg%averaging_mode = 'level'
    469479
     
    485495
    486496    init_variables_required = .TRUE.
    487     boundary_variables_required = TRIM( cfg%bc_mode ) == 'real'
    488     ls_forcing_variables_required = TRIM( cfg%bc_mode ) == 'ideal'
     497    boundary_variables_required = (                                            &
     498       ( TRIM( cfg%bc_mode ) == CFG_FORCING_HETERO )  .OR.                     &
     499       ( TRIM( cfg%bc_mode ) == CFG_FORCING_HOMO )                             &
     500    )
     501    ls_forcing_variables_required = TRIM( cfg%bc_mode ) == CFG_FORCING_NUDGING
    489502    surface_forcing_required = .TRUE.
    490503
     
    503516    CALL validate_config( cfg )
    504517
    505     CALL report('setup_parameters', "initialization mode: " // TRIM(cfg%ic_mode))
    506     CALL report('setup_parameters', "       forcing mode: " // TRIM(cfg%bc_mode))
    507     CALL report('setup_parameters', "     averaging mode: " // TRIM(cfg%averaging_mode))
    508     CALL report('setup_parameters', "    averaging angle: " // real_to_str(cfg%averaging_angle))
    509     CALL report('setup_parameters', "    averaging angle: " // real_to_str(cfg%averaging_angle))
    510     CALL report('setup_parameters', "          data path: " // TRIM(cfg%input_path))
    511     CALL report('setup_parameters', "           hhl file: " // TRIM(cfg%hhl_file))
    512     CALL report('setup_parameters', "       soiltyp file: " // TRIM(cfg%soiltyp_file))
    513     CALL report('setup_parameters', "      namelist file: " // TRIM(cfg%namelist_file))
    514     CALL report('setup_parameters', "   output data file: " // TRIM(output_file%name))
     518    CALL report('setup_parameters', "atmosphere initialization mode: " // TRIM(cfg%ic_mode))
     519    CALL report('setup_parameters', "      soil initialization mode: " // TRIM(cfg%isc_mode))
     520    CALL report('setup_parameters', "                  forcing mode: " // TRIM(cfg%bc_mode))
     521    CALL report('setup_parameters', "                averaging mode: " // TRIM(cfg%averaging_mode))
     522    CALL report('setup_parameters', "               averaging angle: " // real_to_str(cfg%averaging_angle))
     523    CALL report('setup_parameters', "               averaging angle: " // real_to_str(cfg%averaging_angle))
     524    CALL report('setup_parameters', "                     data path: " // TRIM(cfg%input_path))
     525    CALL report('setup_parameters', "                      hhl file: " // TRIM(cfg%hhl_file))
     526    CALL report('setup_parameters', "                  soiltyp file: " // TRIM(cfg%soiltyp_file))
     527    CALL report('setup_parameters', "                 namelist file: " // TRIM(cfg%namelist_file))
     528    CALL report('setup_parameters', "              output data file: " // TRIM(output_file%name))
    515529    IF (cfg%process_precipitation )  THEN
    516530        CALL report('setup_parameters', "      precipitation: enabled")
     
    557571       cfg%input_path, flow_prefix, flow_suffix, flow_files)
    558572    CALL get_input_file_list(                                                  &
    559        cfg%start_date, start_hour_soil, end_hour, step_hour,                   &
     573       cfg%start_date, start_hour_flow, start_hour_flow, step_hour,            &
    560574       cfg%input_path, soil_prefix, soil_suffix, soil_files)
    561575    CALL get_input_file_list(                                                  &
     
    10971111    ENDIF
    10981112
    1099 
    1100     CALL init_averaging_grid(averaged_initial_scalar_profile, cosmo_grid,   &
     1113    CALL init_averaging_grid(averaged_soil_profile, cosmo_grid,             &
     1114            x = 0.5_wp * lx, y = 0.5_wp * ly, z = depths, z0 = z0,          &
     1115            lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
     1116            latmin = latmin_palm, latmax = latmax_palm,                     &
     1117            kind='scalar', name='averaged soil profile')
     1118
     1119    CALL init_averaging_grid(averaged_scalar_profile, cosmo_grid,           &
    11011120            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11021121            lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
    11031122            latmin = latmin_palm, latmax = latmax_palm,                     &
    1104             kind='scalar', name='averaged initial scalar')
    1105 
    1106     CALL init_averaging_grid(averaged_initial_w_profile, cosmo_grid,        &
     1123            kind='scalar', name='averaged scalar profile')
     1124
     1125    CALL init_averaging_grid(averaged_w_profile, cosmo_grid,                &
    11071126            x = 0.5_wp * lx, y = 0.5_wp * ly, z = zw, z0 = z0,              &
    11081127            lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
    11091128            latmin = latmin_palm, latmax = latmax_palm,                     &
    1110             kind='w', name='averaged initial w')
    1111 
    1112     CALL init_averaging_grid(averaged_scalar_profile, cosmo_grid,           &
     1129            kind='w', name='averaged w profile')
     1130
     1131    CALL init_averaging_grid(averaged_scalar_top_point, cosmo_grid,         &
     1132            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z_top, z0 = z0,           &
     1133            lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
     1134            latmin = latmin_palm, latmax = latmax_palm,                     &
     1135            kind='scalar', name='averaged scalar top point')
     1136
     1137    CALL init_averaging_grid(averaged_w_top_point, cosmo_grid,              &
     1138            x = 0.5_wp * lx, y = 0.5_wp * ly, z = zw_top, z0 = z0,          &
     1139            lonmin = lonmin_palm, lonmax = lonmax_palm,                     &
     1140            latmin = latmin_palm, latmax = latmax_palm,                     &
     1141            kind='w', name='averaged w top point')
     1142
     1143    CALL init_averaging_grid(geostrophic_scalar_profile, cosmo_grid,           &
    11131144            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11141145            lonmin = lam_west, lonmax = lam_east,                           &
    11151146            latmin = phi_south, latmax = phi_north,                         &
    1116             kind='scalar', name='centre geostrophic scalar')
    1117 
    1118     CALL init_averaging_grid(averaged_w_profile, cosmo_grid,                &
     1147            kind='scalar', name='centre geostrophic scalar profile')
     1148
     1149    CALL init_averaging_grid(geostrophic_w_profile, cosmo_grid,                &
    11191150            x = 0.5_wp * lx, y = 0.5_wp * ly, z = zw, z0 = z0,              &
    11201151            lonmin = lam_west, lonmax = lam_east,                           &
    11211152            latmin = phi_south, latmax = phi_north,                         &
    1122             kind='w', name='centre geostrophic w')
    1123 
    1124     CALL init_averaging_grid(south_averaged_scalar_profile, cosmo_grid,     &
     1153            kind='w', name='centre geostrophic w profile')
     1154
     1155    CALL init_averaging_grid(south_geostrophic_scalar_profile, cosmo_grid,     &
    11251156            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11261157            lonmin = lam_west, lonmax = lam_east,                           &
    11271158            latmin = phi_centre - averaging_angle,                          &
    11281159            latmax = phi_centre,                                            &
    1129             kind='scalar', name='south geostrophic scalar')
    1130 
    1131     CALL init_averaging_grid(north_averaged_scalar_profile, cosmo_grid,     &
     1160            kind='scalar', name='south geostrophic scalar profile')
     1161
     1162    CALL init_averaging_grid(north_geostrophic_scalar_profile, cosmo_grid,     &
    11321163            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11331164            lonmin = lam_west, lonmax = lam_east,                           &
    11341165            latmin = phi_centre,                                            &
    11351166            latmax = phi_centre + averaging_angle,                          &
    1136             kind='scalar', name='north geostrophic scalar')
    1137 
    1138     CALL init_averaging_grid(west_averaged_scalar_profile, cosmo_grid,      &
     1167            kind='scalar', name='north geostrophic scalar profile')
     1168
     1169    CALL init_averaging_grid(west_geostrophic_scalar_profile, cosmo_grid,      &
    11391170            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11401171            lonmin = lam_centre - averaging_angle,                          &
    11411172            lonmax = lam_centre,                                            &
    11421173            latmin = phi_south, latmax = phi_north,                         &
    1143             kind='scalar', name='west geostrophic scalar')
    1144 
    1145     CALL init_averaging_grid(east_averaged_scalar_profile, cosmo_grid,      &
     1174            kind='scalar', name='west geostrophic scalar profile')
     1175
     1176    CALL init_averaging_grid(east_geostrophic_scalar_profile, cosmo_grid,      &
    11461177            x = 0.5_wp * lx, y = 0.5_wp * ly, z = z, z0 = z0,               &
    11471178            lonmin = lam_centre,                                            &
    11481179            lonmax = lam_centre + averaging_angle,                          &
    11491180            latmin = phi_south, latmax = phi_north,                         &
    1150             kind='scalar', name='east geostrophic scalar')
     1181            kind='scalar', name='east geostrophic scalar profile')
    11511182
    11521183
     
    11951226    ENDIF
    11961227
    1197     IF (TRIM(cfg%ic_mode) == 'profile')  THEN
     1228    IF (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)  THEN
    11981229        !TODO: remove this conditional if not needed.
    11991230    ENDIF
     
    12851316    setup_volumetric = .TRUE.
    12861317    IF (PRESENT(ic_mode))  THEN
    1287        IF (TRIM(ic_mode) == 'profile')  setup_volumetric = .FALSE.
     1318       IF (TRIM(ic_mode) == CFG_INIT_PROFILE)  setup_volumetric = .FALSE.
    12881319    ENDIF
    12891320
     
    13741405!     
    13751406!--       Allocate neighbour indices and weights
    1376           IF (TRIM(ic_mode) .NE. 'profile')  THEN
     1407          IF (TRIM(ic_mode) .NE. CFG_INIT_PROFILE)  THEN
    13771408             ALLOCATE( grid%kk(0:nx, 0:ny, 1:nz, 2) )
    13781409             grid%kk(:,:,:,:) = -1
     
    14461477!     
    14471478!--       Allocate neighbour indices and weights
    1448           IF (TRIM(ic_mode) .NE. 'profile')  THEN
     1479          IF (TRIM(ic_mode) .NE. CFG_INIT_PROFILE)  THEN
    14491480             ALLOCATE( grid%kk(0:nx, 0:ny, 1:nz, 2) )
    14501481             grid%kk(:,:,:,:) = -1
     
    18581889    IF ( ANY( min_dz_stretch_level_end(1:number_stretch_level_start) >      &
    18591890              dz_stretch_level_end(1:number_stretch_level_start) ) )  THEN
    1860     !IF ( ANY( min_dz_stretch_level_end >      &
    1861     !          dz_stretch_level_end ) ) THEN
    18621891          message = 'Each dz_stretch_level_end has to be larger '  // &
    18631892                    'than its corresponding value for ' //            &
     
    23692398                      invar%to_be_processed = .FALSE.
    23702399                      outvar%to_be_processed = .FALSE.
    2371                       message = "Optional output variable '" // TRIM( outvar%name ) // "' was deactivated" // &
    2372                          " because the corresponding input variable was not found in file '" // TRIM( filename ) // "'."
     2400                      message = "Skipping optional output variable '" // TRIM( outvar%name ) // &
     2401                         ", corresponding input variable not available in file '" // TRIM( filename ) // "'."
    23732402                      CALL warn( 'validate_io_groups', message )
    23742403                ENDIF
    23752404             ENDIF
    23762405
    2377              !IF ( .NOT.netcdf_variable_present_in_file( invar%name, filename ) )  THEN
    2378 !--          !      abort due to missing input variable
    2379              !      message = "The mandatory input variable '" // TRIM( invar%name ) // &
    2380              !         " was not found in the input file '" // TRIM( filename ) // "'."
    2381              !      CALL inifor_abort( 'validate_io_groups', message  )
    2382              !   ENDIF
    2383              !IF ( .NOT.netcdf_variable_present_in_file( invar%name, filename ) )  THEN
    2384 !--          !      abort due to missing input variable
    2385              !      message = "The mandatory input variable '" // TRIM( invar%name ) // &
    2386              !         " was not found in the input file '" // TRIM( filename ) // "'."
    2387              !      CALL inifor_abort( 'validate_io_groups', message  )
    2388              !   ENDIF
    2389              !ENDIF
    23902406!--       outvar loop
    23912407          ENDDO
     
    24932509!> Initializes the variable list.
    24942510!------------------------------------------------------------------------------!
    2495  SUBROUTINE setup_variable_tables(ic_mode)
    2496     CHARACTER(LEN=*), INTENT(IN) ::  ic_mode
    2497     INTEGER(iwp)                 ::  n_invar = 0  !< number of variables in the input variable table
    2498     INTEGER(iwp)                 ::  n_outvar = 0 !< number of variables in the output variable table
    2499     TYPE(nc_var), POINTER        ::  var
     2511 SUBROUTINE setup_variable_tables
     2512    INTEGER(iwp)                    ::  n_invar = 0  !< number of variables in the input variable table
     2513    INTEGER(iwp)                    ::  n_outvar = 0 !< number of variables in the output variable table
     2514    TYPE(nc_var), POINTER           ::  var
    25002515
    25012516    IF (TRIM(cfg%start_date) == '')  THEN
     
    26262641       output_file       = output_file,                                     &
    26272642       grid              = palm_grid,                                       &
    2628        intermediate_grid = palm_intermediate                                &
     2643       intermediate_grid = palm_intermediate,                               &
     2644       is_profile = (TRIM(cfg%isc_mode) == CFG_INIT_SOIL_PROFILE)           &
    26292645    )
    26302646
     
    26382654       output_file       = output_file,                                     &
    26392655       grid              = palm_grid,                                       &
    2640        intermediate_grid = palm_intermediate                                &
     2656       intermediate_grid = palm_intermediate,                               &
     2657       is_profile = (TRIM(cfg%isc_mode) == CFG_INIT_SOIL_PROFILE)           &
    26412658    )
    26422659
     
    26512668       grid              = palm_grid,                                       &
    26522669       intermediate_grid = palm_intermediate,                               &
    2653        is_profile = (TRIM(ic_mode) == 'profile')                            &
    2654     )
    2655     IF (TRIM(ic_mode) == 'profile')  THEN
    2656        output_var_table(3)%averaging_grid => averaged_initial_scalar_profile
    2657     ENDIF
     2670       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     2671    )
    26582672
    26592673    output_var_table(4) = init_nc_var(                                      &
     
    26662680       grid              = scalars_west_grid,                               &
    26672681       intermediate_grid = scalars_west_intermediate,                       &
     2682       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO),                &
    26682683       output_file = output_file                                            &
    26692684    )
     
    26782693       grid              = scalars_east_grid,                               &
    26792694       intermediate_grid = scalars_east_intermediate,                       &
     2695       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO),                &
    26802696       output_file = output_file                                            &
    26812697    )
     
    26902706       grid              = scalars_north_grid,                              &
    26912707       intermediate_grid = scalars_north_intermediate,                      &
     2708       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO),                &
    26922709       output_file = output_file                                            &
    26932710    )
     
    27022719       grid              = scalars_south_grid,                              &
    27032720       intermediate_grid = scalars_south_intermediate,                      &
     2721       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO),                &
    27042722       output_file = output_file                                            &
    27052723    )
     
    27142732       grid              = scalars_top_grid,                                &
    27152733       intermediate_grid = scalars_top_intermediate,                        &
     2734       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO),                &
    27162735       output_file = output_file                                            &
    27172736    )
     
    27272746       grid              = palm_grid,                                       &
    27282747       intermediate_grid = palm_intermediate,                               &
    2729        is_profile = (TRIM(ic_mode) == 'profile')                            &
    2730     )
    2731     IF (TRIM(ic_mode) == 'profile')  THEN
    2732        output_var_table(9)%averaging_grid => averaged_initial_scalar_profile
    2733     ENDIF
     2748       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     2749    )
    27342750
    27352751    output_var_table(10) = init_nc_var(                                     &
     
    27422758       output_file       = output_file,                                     &
    27432759       grid              = scalars_west_grid,                               &
    2744        intermediate_grid = scalars_west_intermediate                        &
     2760       intermediate_grid = scalars_west_intermediate,                       &
     2761       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    27452762    )
    27462763
     
    27542771       output_file       = output_file,                                     &
    27552772       grid              = scalars_east_grid,                               &
    2756        intermediate_grid = scalars_east_intermediate                        &
     2773       intermediate_grid = scalars_east_intermediate,                       &
     2774       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    27572775    )
    27582776
     
    27662784       output_file       = output_file,                                     &
    27672785       grid              = scalars_north_grid,                              &
    2768        intermediate_grid = scalars_north_intermediate                       &
     2786       intermediate_grid = scalars_north_intermediate,                      &
     2787       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    27692788    )
    27702789
     
    27782797       output_file       = output_file,                                     &
    27792798       grid              = scalars_south_grid,                              &
    2780        intermediate_grid = scalars_south_intermediate                       &
     2799       intermediate_grid = scalars_south_intermediate,                      &
     2800       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    27812801    )
    27822802
     
    27902810       output_file       = output_file,                                     &
    27912811       grid              = scalars_top_grid,                                &
    2792        intermediate_grid = scalars_top_intermediate                         &
     2812       intermediate_grid = scalars_top_intermediate,                        &
     2813       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    27932814    )
    27942815
     
    28032824       grid              = u_initial_grid,                                  &
    28042825       intermediate_grid = u_initial_intermediate,                          &
    2805        is_profile = (TRIM(ic_mode) == 'profile')                            &
    2806     )
    2807     IF (TRIM(ic_mode) == 'profile')  THEN
    2808        output_var_table(15)%averaging_grid => averaged_initial_scalar_profile
    2809     ENDIF
     2826       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     2827    )
    28102828
    28112829    output_var_table(16) = init_nc_var(                                     &
     
    28182836       output_file       = output_file,                                     &
    28192837       grid              = u_west_grid,                                     &
    2820        intermediate_grid = u_west_intermediate                              &
     2838       intermediate_grid = u_west_intermediate,                             &
     2839       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28212840    )
    28222841
     
    28302849       output_file       = output_file,                                     &
    28312850       grid              = u_east_grid,                                     &
    2832        intermediate_grid = u_east_intermediate                              &
     2851       intermediate_grid = u_east_intermediate,                             &
     2852       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28332853    )
    28342854
     
    28422862       output_file       = output_file,                                     &
    28432863       grid              = u_north_grid,                                    &
    2844        intermediate_grid = u_north_intermediate                             &
     2864       intermediate_grid = u_north_intermediate,                            &
     2865       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28452866    )
    28462867
     
    28542875       output_file       = output_file,                                     &
    28552876       grid              = u_south_grid,                                    &
    2856        intermediate_grid = u_south_intermediate                             &
     2877       intermediate_grid = u_south_intermediate,                            &
     2878       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28572879    )
    28582880
     
    28662888       output_file       = output_file,                                     &
    28672889       grid              = u_top_grid,                                      &
    2868        intermediate_grid = u_top_intermediate                               &
     2890       intermediate_grid = u_top_intermediate,                              &
     2891       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28692892    )
    28702893
     
    28792902       grid              = v_initial_grid,                                  &
    28802903       intermediate_grid = v_initial_intermediate,                          &
    2881        is_profile = (TRIM(ic_mode) == 'profile')                            &
    2882     )
    2883     IF (TRIM(ic_mode) == 'profile')  THEN
    2884        output_var_table(21)%averaging_grid => averaged_initial_scalar_profile
    2885     ENDIF
     2904       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     2905    )
    28862906
    28872907    output_var_table(22) = init_nc_var(                                     &
     
    28942914       output_file       = output_file,                                     &
    28952915       grid              = v_west_grid,                                     &
    2896        intermediate_grid = v_west_intermediate                              &
     2916       intermediate_grid = v_west_intermediate,                             &
     2917       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    28972918    )
    28982919
     
    29062927       output_file       = output_file,                                     &
    29072928       grid              = v_east_grid,                                     &
    2908        intermediate_grid = v_east_intermediate                              &
     2929       intermediate_grid = v_east_intermediate,                             &
     2930       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29092931    )
    29102932
     
    29182940       output_file       = output_file,                                     &
    29192941       grid              = v_north_grid,                                    &
    2920        intermediate_grid = v_north_intermediate                             &
     2942       intermediate_grid = v_north_intermediate,                            &
     2943       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29212944    )
    29222945
     
    29302953       output_file       = output_file,                                     &
    29312954       grid              = v_south_grid,                                    &
    2932        intermediate_grid = v_south_intermediate                             &
     2955       intermediate_grid = v_south_intermediate,                            &
     2956       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29332957    )
    29342958
     
    29422966       output_file       = output_file,                                     &
    29432967       grid              = v_top_grid,                                      &
    2944        intermediate_grid = v_top_intermediate                               &
     2968       intermediate_grid = v_top_intermediate,                              &
     2969       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29452970    )
    29462971
     
    29552980       grid              = w_initial_grid,                                  &
    29562981       intermediate_grid = w_initial_intermediate,                          &
    2957        is_profile = (TRIM(ic_mode) == 'profile')                            &
    2958     )
    2959     IF (TRIM(ic_mode) == 'profile')  THEN
    2960        output_var_table(27)%averaging_grid => averaged_initial_w_profile
    2961     ENDIF
     2982       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     2983    )
    29622984
    29632985    output_var_table(28) = init_nc_var(                                     &
     
    29702992       output_file       = output_file,                                     &
    29712993       grid              = w_west_grid,                                     &
    2972        intermediate_grid = w_west_intermediate                              &
     2994       intermediate_grid = w_west_intermediate,                             &
     2995       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29732996    )
    29742997
     
    29823005       output_file       = output_file,                                     &
    29833006       grid              = w_east_grid,                                     &
    2984        intermediate_grid = w_east_intermediate                              &
     3007       intermediate_grid = w_east_intermediate,                             &
     3008       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29853009    )
    29863010
     
    29943018       output_file       = output_file,                                     &
    29953019       grid              = w_north_grid,                                    &
    2996        intermediate_grid = w_north_intermediate                             &
     3020       intermediate_grid = w_north_intermediate,                            &
     3021       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    29973022    )
    29983023
     
    30063031       output_file       = output_file,                                     &
    30073032       grid              = w_south_grid,                                    &
    3008        intermediate_grid = w_south_intermediate                             &
     3033       intermediate_grid = w_south_intermediate,                            &
     3034       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    30093035    )
    30103036
     
    30183044       output_file       = output_file,                                     &
    30193045       grid              = w_top_grid,                                      &
    3020        intermediate_grid = w_top_intermediate                               &
     3046       intermediate_grid = w_top_intermediate,                              &
     3047       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    30213048    )
    30223049
     
    31433170       intermediate_grid = palm_intermediate                                &
    31443171    )
    3145     output_var_table(42)%averaging_grid => averaged_scalar_profile
     3172    output_var_table(42)%averaging_grid => geostrophic_scalar_profile
    31463173
    31473174    output_var_table(43) = init_nc_var(                                     &
     
    31533180       input_id          = 1_iwp,                                           &
    31543181       output_file       = output_file,                                     &
    3155        grid              = averaged_scalar_profile,                         &
    3156        intermediate_grid = averaged_scalar_profile                          &
     3182       grid              = geostrophic_scalar_profile,                         &
     3183       intermediate_grid = geostrophic_scalar_profile                          &
    31573184    )
    31583185
     
    31653192       input_id          = 1_iwp,                                           &
    31663193       output_file       = output_file,                                     &
    3167        grid              = averaged_scalar_profile,                         &
    3168        intermediate_grid = averaged_scalar_profile                          &
     3194       grid              = geostrophic_scalar_profile,                         &
     3195       intermediate_grid = geostrophic_scalar_profile                          &
    31693196    )
    31703197
     
    31773204       input_id          = 1_iwp,                                           &
    31783205       output_file       = output_file,                                     &
    3179        grid              = averaged_scalar_profile,                         &
    3180        intermediate_grid = averaged_scalar_profile                          &
     3206       grid              = geostrophic_scalar_profile,                         &
     3207       intermediate_grid = geostrophic_scalar_profile                          &
    31813208    )
    31823209    output_var_table(45)%to_be_processed = ls_forcing_variables_required
     
    31903217       input_id          = 1_iwp,                                           &
    31913218       output_file       = output_file,                                     &
    3192        grid              = averaged_scalar_profile,                         &
    3193        intermediate_grid = averaged_scalar_profile                          &
     3219       grid              = geostrophic_scalar_profile,                         &
     3220       intermediate_grid = geostrophic_scalar_profile                          &
    31943221    )
    31953222    output_var_table(46)%to_be_processed = ls_forcing_variables_required
     
    32033230       input_id          = 1_iwp,                                           &
    32043231       output_file       = output_file,                                     &
    3205        grid              = averaged_scalar_profile,                         &
    3206        intermediate_grid = averaged_scalar_profile                          &
     3232       grid              = geostrophic_scalar_profile,                         &
     3233       intermediate_grid = geostrophic_scalar_profile                          &
    32073234    )
    32083235    output_var_table(47)%to_be_processed = ls_forcing_variables_required
     
    32163243       input_id          = 1_iwp,                                           &
    32173244       output_file       = output_file,                                     &
    3218        grid              = averaged_w_profile,                              &
    3219        intermediate_grid = averaged_w_profile                               &
     3245       grid              = geostrophic_w_profile,                              &
     3246       intermediate_grid = geostrophic_w_profile                               &
    32203247    )
    32213248    output_var_table(48)%to_be_processed = ls_forcing_variables_required
     
    32303257       input_id          = 1_iwp,                                           &
    32313258       output_file       = output_file,                                     &
    3232        grid              = averaged_scalar_profile,                         &
    3233        intermediate_grid = averaged_scalar_profile                          &
     3259       grid              = geostrophic_scalar_profile,                         &
     3260       intermediate_grid = geostrophic_scalar_profile                          &
    32343261    )
    32353262    output_var_table(49)%to_be_processed = ls_forcing_variables_required
     
    32433270       input_id          = 1_iwp,                                           &
    32443271       output_file       = output_file,                                     &
    3245        grid              = averaged_scalar_profile,                         &
    3246        intermediate_grid = averaged_scalar_profile                          &
     3272       grid              = geostrophic_scalar_profile,                         &
     3273       intermediate_grid = geostrophic_scalar_profile                          &
    32473274    )
    32483275    output_var_table(50)%to_be_processed = ls_forcing_variables_required
     
    32563283       input_id          = 1_iwp,                                           &
    32573284       output_file       = output_file,                                     &
    3258        grid              = averaged_scalar_profile,                         &
    3259        intermediate_grid = averaged_scalar_profile                          &
     3285       grid              = geostrophic_scalar_profile,                         &
     3286       intermediate_grid = geostrophic_scalar_profile                          &
    32603287    )
    32613288    output_var_table(51)%to_be_processed = ls_forcing_variables_required
     
    32693296       input_id          = 3_iwp,                                           &
    32703297       output_file       = output_file,                                     &
    3271        grid              = averaged_scalar_profile,                         &
    3272        intermediate_grid = averaged_scalar_profile                          &
     3298       grid              = geostrophic_scalar_profile,                         &
     3299       intermediate_grid = geostrophic_scalar_profile                          &
    32733300    )
    32743301    output_var_table(52)%to_be_processed = ls_forcing_variables_required
     
    32833310       input_id          = 3_iwp,                                           &
    32843311       output_file       = output_file,                                     &
    3285        grid              = averaged_scalar_profile,                         &
    3286        intermediate_grid = averaged_scalar_profile                          &
     3312       grid              = geostrophic_scalar_profile,                         &
     3313       intermediate_grid = geostrophic_scalar_profile                          &
    32873314    )
    32883315    output_var_table(53)%to_be_processed = ls_forcing_variables_required
     
    32963323       input_id          = 3_iwp,                                           &
    32973324       output_file       = output_file,                                     &
    3298        grid              = averaged_scalar_profile,                         &
    3299        intermediate_grid = averaged_scalar_profile                          &
     3325       grid              = geostrophic_scalar_profile,                         &
     3326       intermediate_grid = geostrophic_scalar_profile                          &
    33003327    )
    33013328    output_var_table(54)%to_be_processed = ls_forcing_variables_required
     
    33093336       input_id          = 1_iwp,                                           &
    33103337       output_file       = output_file,                                     &
    3311        grid              = averaged_scalar_profile,                         &
    3312        intermediate_grid = averaged_scalar_profile                          &
     3338       grid              = geostrophic_scalar_profile,                         &
     3339       intermediate_grid = geostrophic_scalar_profile                          &
    33133340    )
    33143341    output_var_table(55)%to_be_processed = ls_forcing_variables_required
     
    33163343
    33173344    output_var_table(56) = init_nc_var(                                     &
    3318        name              = 'internal_density_centre',                              &
     3345       name              = 'internal_density_centre',                       &
    33193346       std_name          = "",                                              &
    33203347       long_name         = "",                                              &
     
    33233350       input_id          = 4_iwp,                                           &
    33243351       output_file       = output_file,                                     &
    3325        grid              = averaged_scalar_profile,                         &
    3326        intermediate_grid = averaged_scalar_profile                          &
    3327     )
    3328     output_var_table(56)%averaging_grid => averaged_scalar_profile
     3352       grid              = geostrophic_scalar_profile,                         &
     3353       intermediate_grid = geostrophic_scalar_profile                          &
     3354    )
     3355    output_var_table(56)%averaging_grid => geostrophic_scalar_profile
    33293356
    33303357
    33313358    output_var_table(57) = init_nc_var(                                     &
    3332        name              = 'internal_density_north',                       &
     3359       name              = 'internal_density_north',                        &
    33333360       std_name          = "",                                              &
    33343361       long_name         = "",                                              &
     
    33373364       input_id          = 4_iwp,                                           &
    33383365       output_file       = output_file,                                     &
    3339        grid              = north_averaged_scalar_profile,                   &
    3340        intermediate_grid = north_averaged_scalar_profile                    &
    3341     )
    3342     output_var_table(57)%averaging_grid => north_averaged_scalar_profile
     3366       grid              = north_geostrophic_scalar_profile,                   &
     3367       intermediate_grid = north_geostrophic_scalar_profile                    &
     3368    )
     3369    output_var_table(57)%averaging_grid => north_geostrophic_scalar_profile
    33433370    output_var_table(57)%to_be_processed = .NOT. cfg%ug_defined_by_user
    33443371
    33453372
    33463373    output_var_table(58) = init_nc_var(                                     &
    3347        name              = 'internal_density_south',                       &
     3374       name              = 'internal_density_south',                        &
    33483375       std_name          = "",                                              &
    33493376       long_name         = "",                                              &
     
    33523379       input_id          = 4_iwp,                                           &
    33533380       output_file       = output_file,                                     &
    3354        grid              = south_averaged_scalar_profile,                   &
    3355        intermediate_grid = south_averaged_scalar_profile                    &
    3356     )
    3357     output_var_table(58)%averaging_grid => south_averaged_scalar_profile
     3381       grid              = south_geostrophic_scalar_profile,                   &
     3382       intermediate_grid = south_geostrophic_scalar_profile                    &
     3383    )
     3384    output_var_table(58)%averaging_grid => south_geostrophic_scalar_profile
    33583385    output_var_table(58)%to_be_processed = .NOT. cfg%ug_defined_by_user
    33593386
    33603387
    33613388    output_var_table(59) = init_nc_var(                                     &
    3362        name              = 'internal_density_east',                        &
     3389       name              = 'internal_density_east',                         &
    33633390       std_name          = "",                                              &
    33643391       long_name         = "",                                              &
     
    33673394       input_id          = 4_iwp,                                           &
    33683395       output_file       = output_file,                                     &
    3369        grid              = east_averaged_scalar_profile,                    &
    3370        intermediate_grid = east_averaged_scalar_profile                     &
    3371     )
    3372     output_var_table(59)%averaging_grid => east_averaged_scalar_profile
     3396       grid              = east_geostrophic_scalar_profile,                    &
     3397       intermediate_grid = east_geostrophic_scalar_profile                     &
     3398    )
     3399    output_var_table(59)%averaging_grid => east_geostrophic_scalar_profile
    33733400    output_var_table(59)%to_be_processed = .NOT. cfg%ug_defined_by_user
    33743401
    33753402
    33763403    output_var_table(60) = init_nc_var(                                     &
    3377        name              = 'internal_density_west',                        &
     3404       name              = 'internal_density_west',                         &
    33783405       std_name          = "",                                              &
    33793406       long_name         = "",                                              &
     
    33823409       input_id          = 4_iwp,                                           &
    33833410       output_file       = output_file,                                     &
    3384        grid              = west_averaged_scalar_profile,                    &
    3385        intermediate_grid = west_averaged_scalar_profile                     &
    3386     )
    3387     output_var_table(60)%averaging_grid => west_averaged_scalar_profile
     3411       grid              = west_geostrophic_scalar_profile,                    &
     3412       intermediate_grid = west_geostrophic_scalar_profile                     &
     3413    )
     3414    output_var_table(60)%averaging_grid => west_geostrophic_scalar_profile
    33883415    output_var_table(60)%to_be_processed = .NOT. cfg%ug_defined_by_user
    33893416
     
    33963423       input_id          = 2_iwp,                                           &
    33973424       output_file       = output_file,                                     &
    3398        grid              = north_averaged_scalar_profile,                   &
    3399        intermediate_grid = north_averaged_scalar_profile                    &
    3400     )
    3401     output_var_table(61)%averaging_grid => north_averaged_scalar_profile
     3425       grid              = north_geostrophic_scalar_profile,                   &
     3426       intermediate_grid = north_geostrophic_scalar_profile                    &
     3427    )
     3428    output_var_table(61)%averaging_grid => north_geostrophic_scalar_profile
    34023429    output_var_table(61)%to_be_processed = .NOT. cfg%ug_defined_by_user
    34033430
     
    34113438       input_id          = 2_iwp,                                           &
    34123439       output_file       = output_file,                                     &
    3413        grid              = south_averaged_scalar_profile,                   &
    3414        intermediate_grid = south_averaged_scalar_profile                    &
    3415     )
    3416     output_var_table(62)%averaging_grid => south_averaged_scalar_profile
     3440       grid              = south_geostrophic_scalar_profile,                   &
     3441       intermediate_grid = south_geostrophic_scalar_profile                    &
     3442    )
     3443    output_var_table(62)%averaging_grid => south_geostrophic_scalar_profile
    34173444    output_var_table(62)%to_be_processed = .NOT. cfg%ug_defined_by_user
    34183445
     
    34263453       input_id          = 2_iwp,                                           &
    34273454       output_file       = output_file,                                     &
    3428        grid              = east_averaged_scalar_profile,                    &
    3429        intermediate_grid = east_averaged_scalar_profile                     &
    3430     )
    3431     output_var_table(63)%averaging_grid => east_averaged_scalar_profile
     3455       grid              = east_geostrophic_scalar_profile,                    &
     3456       intermediate_grid = east_geostrophic_scalar_profile                     &
     3457    )
     3458    output_var_table(63)%averaging_grid => east_geostrophic_scalar_profile
    34323459    output_var_table(63)%to_be_processed = .NOT. cfg%ug_defined_by_user
    34333460
     
    34413468       input_id          = 2_iwp,                                           &
    34423469       output_file       = output_file,                                     &
    3443        grid              = west_averaged_scalar_profile,                    &
    3444        intermediate_grid = west_averaged_scalar_profile                     &
    3445     )
    3446     output_var_table(64)%averaging_grid => west_averaged_scalar_profile
     3470       grid              = west_geostrophic_scalar_profile,                    &
     3471       intermediate_grid = west_geostrophic_scalar_profile                     &
     3472    )
     3473    output_var_table(64)%averaging_grid => west_geostrophic_scalar_profile
    34473474    output_var_table(64)%to_be_processed = .NOT. cfg%ug_defined_by_user
    34483475
    3449     output_var_table(65) = init_nc_var(                                      &
     3476    output_var_table(65) = init_nc_var(                                     &
    34503477       name              = 'init_atmosphere_qc',                            &
    34513478       std_name          = "",                                              &
     
    34573484       grid              = palm_grid,                                       &
    34583485       intermediate_grid = palm_intermediate,                               &
    3459        is_profile = (TRIM(ic_mode) == 'profile')                            &
    3460     )
    3461     IF (TRIM(ic_mode) == 'profile')  THEN
    3462        output_var_table(65)%averaging_grid => averaged_initial_scalar_profile
    3463     ENDIF
     3486       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     3487    )
    34643488    output_var_table(65)%is_optional = .TRUE.
    34653489
     
    34733497       output_file       = output_file,                                     &
    34743498       grid              = scalars_west_grid,                               &
    3475        intermediate_grid = scalars_west_intermediate                        &
     3499       intermediate_grid = scalars_west_intermediate,                       &
     3500       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    34763501    )
    34773502    output_var_table(66)%is_optional = .TRUE.
     
    34863511       output_file       = output_file,                                     &
    34873512       grid              = scalars_east_grid,                               &
    3488        intermediate_grid = scalars_east_intermediate                        &
     3513       intermediate_grid = scalars_east_intermediate,                       &
     3514       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    34893515    )
    34903516    output_var_table(67)%is_optional = .TRUE.
     
    34993525       output_file       = output_file,                                     &
    35003526       grid              = scalars_north_grid,                              &
    3501        intermediate_grid = scalars_north_intermediate                       &
     3527       intermediate_grid = scalars_north_intermediate,                      &
     3528       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35023529    )
    35033530    output_var_table(68)%is_optional = .TRUE.
     
    35123539       output_file       = output_file,                                     &
    35133540       grid              = scalars_south_grid,                              &
    3514        intermediate_grid = scalars_south_intermediate                       &
     3541       intermediate_grid = scalars_south_intermediate,                      &
     3542       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35153543    )
    35163544    output_var_table(69)%is_optional = .TRUE.
     
    35253553       output_file       = output_file,                                     &
    35263554       grid              = scalars_top_grid,                                &
    3527        intermediate_grid = scalars_top_intermediate                         &
     3555       intermediate_grid = scalars_top_intermediate,                        &
     3556       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35283557    )
    35293558    output_var_table(70)%is_optional = .TRUE.
     
    35393568       grid              = palm_grid,                                       &
    35403569       intermediate_grid = palm_intermediate,                               &
    3541        is_profile = (TRIM(ic_mode) == 'profile')                            &
    3542     )
    3543     IF (TRIM(ic_mode) == 'profile')  THEN
    3544        output_var_table(71)%averaging_grid => averaged_initial_scalar_profile
    3545     ENDIF
     3570       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     3571    )
    35463572    output_var_table(71)%is_optional = .TRUE.
    35473573
     
    35553581       output_file       = output_file,                                     &
    35563582       grid              = scalars_west_grid,                               &
    3557        intermediate_grid = scalars_west_intermediate                        &
     3583       intermediate_grid = scalars_west_intermediate,                       &
     3584       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35583585    )
    35593586    output_var_table(72)%is_optional = .TRUE.
     
    35683595       output_file       = output_file,                                     &
    35693596       grid              = scalars_east_grid,                               &
    3570        intermediate_grid = scalars_east_intermediate                        &
     3597       intermediate_grid = scalars_east_intermediate,                       &
     3598       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35713599    )
    35723600    output_var_table(73)%is_optional = .TRUE.
     
    35813609       output_file       = output_file,                                     &
    35823610       grid              = scalars_north_grid,                              &
    3583        intermediate_grid = scalars_north_intermediate                       &
     3611       intermediate_grid = scalars_north_intermediate,                      &
     3612       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35843613    )
    35853614    output_var_table(74)%is_optional = .TRUE.
     
    35943623       output_file       = output_file,                                     &
    35953624       grid              = scalars_south_grid,                              &
    3596        intermediate_grid = scalars_south_intermediate                       &
     3625       intermediate_grid = scalars_south_intermediate,                      &
     3626       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    35973627    )
    35983628    output_var_table(75)%is_optional = .TRUE.
     
    36073637       output_file       = output_file,                                     &
    36083638       grid              = scalars_top_grid,                                &
    3609        intermediate_grid = scalars_top_intermediate                         &
     3639       intermediate_grid = scalars_top_intermediate,                        &
     3640       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36103641    )
    36113642    output_var_table(76)%is_optional = .TRUE.
     
    36143645       name              = 'init_atmosphere_qr',                            &
    36153646       std_name          = "",                                              &
    3616        long_name         = "initial rain water mixture fraction",            &
     3647       long_name         = "initial rain water mixture fraction",           &
    36173648       units             = "kg/kg",                                         &
    36183649       kind              = "init scalar",                                   &
     
    36213652       grid              = palm_grid,                                       &
    36223653       intermediate_grid = palm_intermediate,                               &
    3623        is_profile = (TRIM(ic_mode) == 'profile')                            &
    3624     )
    3625     IF (TRIM(ic_mode) == 'profile')  THEN
    3626        output_var_table(77)%averaging_grid => averaged_initial_scalar_profile
    3627     ENDIF
     3654       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     3655    )
    36283656    output_var_table(77)%is_optional = .TRUE.
    36293657
     
    36373665       output_file       = output_file,                                     &
    36383666       grid              = scalars_west_grid,                               &
    3639        intermediate_grid = scalars_west_intermediate                        &
     3667       intermediate_grid = scalars_west_intermediate,                       &
     3668       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36403669    )
    36413670    output_var_table(78)%is_optional = .TRUE.
     
    36503679       output_file       = output_file,                                     &
    36513680       grid              = scalars_east_grid,                               &
    3652        intermediate_grid = scalars_east_intermediate                        &
     3681       intermediate_grid = scalars_east_intermediate,                       &
     3682       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36533683    )
    36543684    output_var_table(79)%is_optional = .TRUE.
     
    36633693       output_file       = output_file,                                     &
    36643694       grid              = scalars_north_grid,                              &
    3665        intermediate_grid = scalars_north_intermediate                       &
     3695       intermediate_grid = scalars_north_intermediate,                      &
     3696       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36663697    )
    36673698    output_var_table(80)%is_optional = .TRUE.
     
    36763707       output_file       = output_file,                                     &
    36773708       grid              = scalars_south_grid,                              &
    3678        intermediate_grid = scalars_south_intermediate                       &
     3709       intermediate_grid = scalars_south_intermediate,                      &
     3710       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36793711    )
    36803712    output_var_table(81)%is_optional = .TRUE.
     
    36893721       output_file       = output_file,                                     &
    36903722       grid              = scalars_top_grid,                                &
    3691        intermediate_grid = scalars_top_intermediate                         &
     3723       intermediate_grid = scalars_top_intermediate,                        &
     3724       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    36923725    )
    36933726    output_var_table(82)%is_optional = .TRUE.
     
    36963729       name              = 'init_atmosphere_qs',                            &
    36973730       std_name          = "",                                              &
    3698        long_name         = "initial snow mixture fraction",            &
     3731       long_name         = "initial snow mixture fraction",                 &
    36993732       units             = "kg/kg",                                         &
    37003733       kind              = "init scalar",                                   &
     
    37033736       grid              = palm_grid,                                       &
    37043737       intermediate_grid = palm_intermediate,                               &
    3705        is_profile = (TRIM(ic_mode) == 'profile')                            &
    3706     )
    3707     IF (TRIM(ic_mode) == 'profile')  THEN
    3708        output_var_table(83)%averaging_grid => averaged_initial_scalar_profile
    3709     ENDIF
     3738       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     3739    )
    37103740    output_var_table(83)%is_optional = .TRUE.
    37113741
     
    37193749       output_file       = output_file,                                     &
    37203750       grid              = scalars_west_grid,                               &
    3721        intermediate_grid = scalars_west_intermediate                        &
     3751       intermediate_grid = scalars_west_intermediate,                       &
     3752       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    37223753    )
    37233754    output_var_table(84)%is_optional = .TRUE.
     
    37323763       output_file       = output_file,                                     &
    37333764       grid              = scalars_east_grid,                               &
    3734        intermediate_grid = scalars_east_intermediate                        &
     3765       intermediate_grid = scalars_east_intermediate,                       &
     3766       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    37353767    )
    37363768    output_var_table(85)%is_optional = .TRUE.
     
    37453777       output_file       = output_file,                                     &
    37463778       grid              = scalars_north_grid,                              &
    3747        intermediate_grid = scalars_north_intermediate                       &
     3779       intermediate_grid = scalars_north_intermediate,                      &
     3780       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    37483781    )
    37493782    output_var_table(86)%is_optional = .TRUE.
     
    37583791       output_file       = output_file,                                     &
    37593792       grid              = scalars_south_grid,                              &
    3760        intermediate_grid = scalars_south_intermediate                       &
     3793       intermediate_grid = scalars_south_intermediate,                      &
     3794       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    37613795    )
    37623796    output_var_table(87)%is_optional = .TRUE.
     
    37713805       output_file       = output_file,                                     &
    37723806       grid              = scalars_top_grid,                                &
    3773        intermediate_grid = scalars_top_intermediate                         &
     3807       intermediate_grid = scalars_top_intermediate,                        &
     3808       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    37743809    )
    37753810    output_var_table(88)%is_optional = .TRUE.
     
    37783813       name              = 'init_atmosphere_qg',                            &
    37793814       std_name          = "",                                              &
    3780        long_name         = "initial graupel mixture fraction",            &
     3815       long_name         = "initial graupel mixture fraction",              &
    37813816       units             = "kg/kg",                                         &
    37823817       kind              = "init scalar",                                   &
     
    37853820       grid              = palm_grid,                                       &
    37863821       intermediate_grid = palm_intermediate,                               &
    3787        is_profile = (TRIM(ic_mode) == 'profile')                            &
    3788     )
    3789     IF (TRIM(ic_mode) == 'profile')  THEN
    3790        output_var_table(89)%averaging_grid => averaged_initial_scalar_profile
    3791     ENDIF
     3822       is_profile = (TRIM(cfg%ic_mode) == CFG_INIT_PROFILE)                 &
     3823    )
    37923824    output_var_table(89)%is_optional = .TRUE.
    37933825
     
    38013833       output_file       = output_file,                                     &
    38023834       grid              = scalars_west_grid,                               &
    3803        intermediate_grid = scalars_west_intermediate                        &
     3835       intermediate_grid = scalars_west_intermediate,                       &
     3836       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    38043837    )
    38053838    output_var_table(90)%is_optional = .TRUE.
     
    38143847       output_file       = output_file,                                     &
    38153848       grid              = scalars_east_grid,                               &
    3816        intermediate_grid = scalars_east_intermediate                        &
     3849       intermediate_grid = scalars_east_intermediate,                       &
     3850       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    38173851    )
    38183852    output_var_table(91)%is_optional = .TRUE.
     
    38273861       output_file       = output_file,                                     &
    38283862       grid              = scalars_north_grid,                              &
    3829        intermediate_grid = scalars_north_intermediate                       &
     3863       intermediate_grid = scalars_north_intermediate,                      &
     3864       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    38303865    )
    38313866    output_var_table(92)%is_optional = .TRUE.
     
    38403875       output_file       = output_file,                                     &
    38413876       grid              = scalars_south_grid,                              &
    3842        intermediate_grid = scalars_south_intermediate                       &
     3877       intermediate_grid = scalars_south_intermediate,                      &
     3878       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    38433879    )
    38443880    output_var_table(93)%is_optional = .TRUE.
     
    38533889       output_file       = output_file,                                     &
    38543890       grid              = scalars_top_grid,                                &
    3855        intermediate_grid = scalars_top_intermediate                         &
     3891       intermediate_grid = scalars_top_intermediate,                        &
     3892       is_profile = (TRIM(cfg%bc_mode) == CFG_FORCING_HOMO)                 &
    38563893    )
    38573894    output_var_table(94)%is_optional = .TRUE.
     
    39694006          var%task            = "interpolate_3d"
    39704007
    3971        CASE( 'init scalar profile', 'init u profile', 'init v profile')
     4008       CASE( 'init soil profile' )
     4009          var%nt              = 1
     4010          var%lod             = 1
     4011          var%ndim            = 1
     4012          var%dimids(1)       = output_file%dimids_soil(3)
     4013          var%dimvarids(1)    = output_file%dimvarids_soil(3)
     4014          var%to_be_processed = init_variables_required
     4015          var%is_internal     = .FALSE.
     4016          var%task            = "average levels"
     4017          var%averaging_grid  => averaged_soil_profile
     4018
     4019       CASE( 'init scalar profile', 'init u profile', 'init v profile' )
    39724020          var%nt              = 1
    39734021          var%lod             = 1
     
    39784026          var%is_internal     = .FALSE.
    39794027          var%task            = "average profile"
     4028          var%averaging_grid  => averaged_scalar_profile
    39804029
    39814030       CASE( 'init w profile')
     
    39884037          var%is_internal     = .FALSE.
    39894038          var%task            = "average profile"
     4039          var%averaging_grid  => averaged_w_profile
    39904040
    39914041       CASE( 'surface forcing' )
    3992           var%lod             = -1
     4042          var%lod             = 2
    39934043          var%ndim            = 3
    39944044          var%dimids(3)       = output_file%dimid_time
     
    40014051
    40024052       CASE( 'left scalar', 'right scalar')
    4003           var%lod             = -1
     4053          var%lod             = 2
    40044054          var%ndim            = 3
    40054055          var%dimids(3)       = output_file%dimid_time
     
    40144064
    40154065       CASE( 'north scalar', 'south scalar')
    4016           var%lod             = -1
     4066          var%lod             = 2
    40174067          var%ndim            = 3
    40184068          var%dimids(3)       = output_file%dimid_time
     
    40274077
    40284078       CASE( 'top scalar', 'top w' )
    4029           var%lod             = -1
     4079          var%lod             = 2
    40304080          var%ndim            = 3
    40314081          var%dimids(3)       = output_file%dimid_time
     
    40404090
    40414091       CASE( 'left u', 'right u' )
    4042           var%lod             = -1
     4092          var%lod             = 2
    40434093          var%ndim            = 3
    40444094          var%dimids(3)       = output_file%dimid_time
     
    40534103
    40544104       CASE( 'north u', 'south u' )
    4055           var%lod             = -1
     4105          var%lod             = 2
    40564106          var%ndim            = 3
    40574107          var%dimids(3)       = output_file%dimid_time    !t
     
    40664116
    40674117       CASE( 'top u' )
    4068           var%lod             = -1
     4118          var%lod             = 2
    40694119          var%ndim            = 3
    40704120          var%dimids(3)       = output_file%dimid_time    !t
     
    40794129
    40804130       CASE( 'left v', 'right v' )
    4081           var%lod             = -1
     4131          var%lod             = 2
    40824132          var%ndim            = 3
    40834133          var%dimids(3)       = output_file%dimid_time
     
    40924142
    40934143       CASE( 'north v', 'south v' )
    4094           var%lod             = -1
     4144          var%lod             = 2
    40954145          var%ndim            = 3
    40964146          var%dimids(3)       = output_file%dimid_time    !t
     
    41054155
    41064156       CASE( 'top v' )
    4107           var%lod             = -1
     4157          var%lod             = 2
    41084158          var%ndim            = 3
    41094159          var%dimids(3)       = output_file%dimid_time    !t
     
    41184168
    41194169       CASE( 'left w', 'right w')
    4120           var%lod             = -1
     4170          var%lod             = 2
    41214171          var%ndim            = 3
    41224172          var%dimids(3)       = output_file%dimid_time
     
    41314181
    41324182       CASE( 'north w', 'south w' )
    4133           var%lod             = -1
     4183          var%lod             = 2
    41344184          var%ndim            = 3
    41354185          var%dimids(3)       = output_file%dimid_time    !t
     
    41434193          var%task            = "interpolate_3d"
    41444194
     4195       CASE( 'left scalar profile', 'right scalar profile',                    &
     4196             'north scalar profile', 'south scalar profile',                   &
     4197             'left u profile', 'right u profile',                              &
     4198             'north u profile', 'south u profile',                             &
     4199             'left v profile', 'right v profile',                              &
     4200             'north v profile', 'south v profile' )
     4201          var%lod             = 1
     4202          var%ndim            = 2
     4203          var%dimids(2)       = output_file%dimid_time    !t
     4204          var%dimids(1)       = output_file%dimids_scl(3) !z
     4205          var%dimvarids(2)    = output_file%dimvarid_time
     4206          var%dimvarids(1)    = output_file%dimvarids_scl(3)
     4207          var%to_be_processed = boundary_variables_required
     4208          var%is_internal     = .FALSE.
     4209          var%task            = "average profile"
     4210          var%averaging_grid  => averaged_scalar_profile
     4211
     4212       CASE( 'top scalar profile', 'top u profile', 'top v profile' )
     4213          var%lod             = 0
     4214          var%ndim            = 1
     4215          var%dimids(1)       = output_file%dimid_time    !t
     4216          var%dimvarids(1)    = output_file%dimvarid_time
     4217          var%to_be_processed = boundary_variables_required
     4218          var%is_internal     = .FALSE.
     4219          var%task            = "average profile"
     4220          var%averaging_grid  => averaged_scalar_top_point
     4221
     4222       CASE( 'left w profile', 'right w profile',                              &
     4223             'north w profile', 'south w profile' )
     4224          var%lod             = 1
     4225          var%ndim            = 2
     4226          var%dimids(2)       = output_file%dimid_time    !t
     4227          var%dimids(1)       = output_file%dimids_vel(3) !z
     4228          var%dimvarids(2)    = output_file%dimvarid_time
     4229          var%dimvarids(1)    = output_file%dimvarids_vel(3)
     4230          var%to_be_processed = boundary_variables_required
     4231          var%is_internal     = .FALSE.
     4232          var%task            = "average profile"
     4233          var%averaging_grid  => averaged_w_profile
     4234
     4235       CASE( 'top w profile' )
     4236          var%lod             = 0
     4237          var%ndim            = 1
     4238          var%dimids(1)       = output_file%dimid_time    !t
     4239          var%dimvarids(1)    = output_file%dimvarid_time
     4240          var%to_be_processed = boundary_variables_required
     4241          var%is_internal     = .FALSE.
     4242          var%task            = "average profile"
     4243          var%averaging_grid  => averaged_w_top_point
     4244
    41454245       CASE( 'time series' )
    41464246          var%lod             = 0
     
    41534253
    41544254       CASE( 'constant scalar profile' )
    4155           var%lod             = -1
     4255          var%lod             = 1
    41564256          var%ndim            = 2
    41574257          var%dimids(2)       = output_file%dimid_time    !t
     
    41644264
    41654265       CASE( 'large-scale scalar forcing' )
    4166           var%lod             = -1
     4266          var%lod             = 1
    41674267          var%ndim            = 2
    41684268          var%dimids(2)       = output_file%dimid_time    !t
     
    41754275
    41764276       CASE( 'geostrophic' )
    4177           var%lod             = -1
     4277          var%lod             = 1
    41784278          var%ndim            = 2
    41794279          var%dimids(2)       = output_file%dimid_time    !t
     
    41864286
    41874287       CASE( 'large-scale w forcing' )
    4188           var%lod             = -1
     4288          var%lod             = 1
    41894289          var%ndim            = 2
    41904290          var%dimids(2)       = output_file%dimid_time    !t
     
    42084308
    42094309       CASE DEFAULT
    4210            message = "Variable kind '" // TRIM(kind) // "' not recognized."
     4310           message = "Variable kind '" // TRIM(out_var_kind) // "' not recognized."
    42114311           CALL inifor_abort ('init_nc_var', message)
    42124312
     
    43504450             DO  i = 1, nx
    43514451
    4352                 CALL get_basic_state(cosmo_grid%hfl(i,j,:), BETA, P_SL, T_SL,&
    4353                                      RD, G, basic_state_pressure)
     4452                CALL get_basic_state( cosmo_grid%hfl(i,j,:), BETA, P_SL, T_SL, &
     4453                                      RD, G, basic_state_pressure )
    43544454
    43554455!
Note: See TracChangeset for help on using the changeset viewer.