Ignore:
Timestamp:
Aug 31, 2020 11:21:17 AM (4 years ago)
Author:
eckhard
Message:

inifor: Support for COSMO cloud water and precipitation

File:
1 edited

Legend:

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

    r4568 r4659  
    2121! Current revisions:
    2222! -----------------
    23 ! 
    24 ! 
     23!
     24!
    2525! Former revisions:
    2626! -----------------
    2727! $Id$
     28! Only define netCDF variables in enabled IO groups
     29! Added cloud and precipitation quantiteis (cloud water, cloud ice, rain, snow
     30!    and graupel content, as well as surface forcings of rain, snow and graupel)
     31! Check for presence of precipitation files
     32! Removed unused code for deaccumulation of summed up and averaged fields
     33! Improved code formatting and documentation
     34!
     35!
     36! 4568 2020-06-19 11:56:30Z eckhard
    2837! Handle COSMO soil data with and without additional surface temperature
    2938! Imporved messaging
     
    180189               PIDS_ORIGIN_Z
    181190    USE inifor_io,                                                             &
    182         ONLY:  get_cosmo_grid, get_input_file_list, get_netcdf_attribute,      &
     191        ONLY:  file_is_present, get_cosmo_grid, get_input_file_list, get_netcdf_attribute,      &
    183192               get_netcdf_dim_vector, get_netcdf_variable, set_palm_origin,    &
    184                parse_command_line_arguments, validate_config,                  &
     193               netcdf_variable_present_in_file, parse_command_line_arguments, validate_config,                  &
    185194               has_surface_value
    186195    USE inifor_transform,                                                      &
     
    287296    INTEGER(iwp) ::  nlev  !< number of levels in target grid (COSMO-DE)
    288297    INTEGER(iwp) ::  ndepths !< number of COSMO-DE soil layers
    289     INTEGER(iwp) ::  start_hour_flow         !< start of flow forcing in number of hours relative to start_date
    290     INTEGER(iwp) ::  start_hour_soil         !< start of soil forcing in number of hours relative to start_date, typically equals start_hour_flow
    291     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
    292     INTEGER(iwp) ::  start_hour_soilmoisture !< start of forcing for the soil moisture spin-up in number of hours relative to start_date, typically -672 (-4 weeks)
     298    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
     300    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
     301    INTEGER(iwp) ::  start_hour_precipitation !< start of forcing for precipitaiton forcing in number of hours relative to start_date
    293302    INTEGER(iwp) ::  end_hour  !< simulation time in hours
    294     INTEGER(iwp) ::  end_hour_soilmoisture  !< end of soil moisture spin-up in hours relative to start_hour_flow
    295303    INTEGER(iwp) ::  step_hour !< number of hours between forcing time steps
    296304
     
    372380    CHARACTER(LEN=LNAME) ::  nc_source_text = ''  !< Text describing the source of the output data, e.g. 'COSMO-DE analysis from ...'
    373381
    374     CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  flow_files          !< list of atmospheric input files (<prefix>YYYYMMDDHH-flow.nc)
    375     CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  soil_moisture_files !< list of precipitation input files (<prefix>YYYYMMDDHH-soilmoisture.nc)
    376     CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  soil_files          !< list of soil input files (temperature, moisture, <prefix>YYYYMMDDHH-soil.nc)
    377     CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  radiation_files     !< list of radiation input files (<prefix>YYYYMMDDHH-rad.nc)
    378 
    379     CHARACTER(LEN=SNAME) ::  input_prefix         !< prefix of input files, e.g. 'laf' for COSMO-DE analyses
    380     CHARACTER(LEN=SNAME) ::  flow_prefix          !< prefix of flow input files, e.g. 'laf' for COSMO-DE analyses
    381     CHARACTER(LEN=SNAME) ::  soil_prefix          !< prefix of soil input files, e.g. 'laf' for COSMO-DE analyses
    382     CHARACTER(LEN=SNAME) ::  radiation_prefix     !< prefix of radiation input files, e.g. 'laf' for COSMO-DE analyses
    383     CHARACTER(LEN=SNAME) ::  soilmoisture_prefix  !< prefix of input files for soil moisture spin-up, e.g. 'laf' for COSMO-DE analyses
    384     CHARACTER(LEN=SNAME) ::  flow_suffix          !< suffix of flow input files, e.g. 'flow'
    385     CHARACTER(LEN=SNAME) ::  soil_suffix          !< suffix of soil input files, e.g. 'soil'
    386     CHARACTER(LEN=SNAME) ::  radiation_suffix     !< suffix of radiation input files, e.g. 'radiation'
    387     CHARACTER(LEN=SNAME) ::  soilmoisture_suffix  !< suffix of input files for soil moisture spin-up, e.g. 'soilmoisture'
     382    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  flow_files      !< list of atmospheric input files (<prefix>YYYYMMDDHH-flow.nc)
     383    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  precip_files    !< list of precipitation input files (<prefix>YYYYMMDDHH-precip.nc)
     384    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  soil_files      !< list of soil input files (temperature, moisture, <prefix>YYYYMMDDHH-soil.nc)
     385    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  radiation_files !< list of radiation input files (<prefix>YYYYMMDDHH-rad.nc)
     386
     387    CHARACTER(LEN=SNAME) ::  input_prefix          !< prefix of input files, e.g. 'laf' for COSMO-DE analyses
     388    CHARACTER(LEN=SNAME) ::  flow_prefix           !< prefix of flow input files, e.g. 'laf' for COSMO-DE analyses
     389    CHARACTER(LEN=SNAME) ::  soil_prefix           !< prefix of soil input files, e.g. 'laf' for COSMO-DE analyses
     390    CHARACTER(LEN=SNAME) ::  radiation_prefix      !< prefix of radiation input files, e.g. 'laf' for COSMO-DE analyses
     391    CHARACTER(LEN=SNAME) ::  precipitation_prefix  !< prefix of input files for precipitation forcing, e.g. 'laf' for COSMO-DE analyses
     392    CHARACTER(LEN=SNAME) ::  flow_suffix           !< suffix of flow input files, e.g. 'flow'
     393    CHARACTER(LEN=SNAME) ::  soil_suffix           !< suffix of soil input files, e.g. 'soil'
     394    CHARACTER(LEN=SNAME) ::  radiation_suffix      !< suffix of radiation input files, e.g. 'radiation'
     395    CHARACTER(LEN=SNAME) ::  precipitation_suffix  !< suffix of input files for precipition forcing, e.g. 'precip'
    388396                         
    389397    TYPE(nc_file) ::  output_file !< metadata of the dynamic driver
     
    408416!------------------------------------------------------------------------------
    409417    cfg%start_date = '2013072100'
    410     end_hour = 2
    411     start_hour_soil = -2
    412     start_hour_soilmoisture = - (4 * 7 * 24) - 2
    413418
    414419!
     
    429434    start_hour_soil = 0
    430435    start_hour_radiation = 0
    431     start_hour_soilmoisture = start_hour_flow - 2
    432     end_hour_soilmoisture = start_hour_flow
     436    start_hour_precipitation = start_hour_flow
    433437    step_hour = FORCING_STEP
    434438
     
    438442    cfg%soil_prefix = input_prefix
    439443    cfg%radiation_prefix = input_prefix
    440     cfg%soilmoisture_prefix  = input_prefix
     444    cfg%precipitation_prefix  = input_prefix
    441445
    442446    flow_suffix = '-flow'
    443447    soil_suffix = '-soil'
    444448    radiation_suffix = '-rad'
    445     soilmoisture_suffix = '-soilmoisture'
     449    precipitation_suffix = '-precip'
    446450
    447451    cfg%debug = .FALSE.
     
    472476    radiation_prefix = TRIM(cfg%input_prefix)
    473477    soil_prefix = TRIM(cfg%input_prefix)
    474     soilmoisture_prefix = TRIM(cfg%input_prefix)
     478    precipitation_prefix = TRIM(cfg%input_prefix)
    475479    IF (cfg%flow_prefix_is_set)  flow_prefix = TRIM(cfg%flow_prefix)
    476480    IF (cfg%radiation_prefix_is_set)  radiation_prefix = TRIM(cfg%radiation_prefix)
    477481    IF (cfg%soil_prefix_is_set)  soil_prefix = TRIM(cfg%soil_prefix)
    478     IF (cfg%soilmoisture_prefix_is_set)  soilmoisture_prefix = TRIM(cfg%soilmoisture_prefix)
     482    IF (cfg%precipitation_prefix_is_set)  precipitation_prefix = TRIM(cfg%precipitation_prefix)
    479483
    480484    output_file%name = cfg%output_file
     
    483487    boundary_variables_required = TRIM( cfg%bc_mode ) == 'real'
    484488    ls_forcing_variables_required = TRIM( cfg%bc_mode ) == 'ideal'
    485     surface_forcing_required = .FALSE.
     489    surface_forcing_required = .TRUE.
    486490
    487491    IF ( ls_forcing_variables_required )  THEN
     
    502506    CALL report('setup_parameters', "       forcing mode: " // TRIM(cfg%bc_mode))
    503507    CALL report('setup_parameters', "     averaging mode: " // TRIM(cfg%averaging_mode))
     508    CALL report('setup_parameters', "    averaging angle: " // real_to_str(cfg%averaging_angle))
    504509    CALL report('setup_parameters', "    averaging angle: " // real_to_str(cfg%averaging_angle))
    505510    CALL report('setup_parameters', "          data path: " // TRIM(cfg%input_path))
     
    508513    CALL report('setup_parameters', "      namelist file: " // TRIM(cfg%namelist_file))
    509514    CALL report('setup_parameters', "   output data file: " // TRIM(output_file%name))
     515    IF (cfg%process_precipitation )  THEN
     516        CALL report('setup_parameters', "      precipitation: enabled")
     517    ELSE
     518        CALL report('setup_parameters', "      precipitation: disabled")
     519    ENDIF
    510520    IF (cfg%debug )  CALL report('setup_parameters', "     debugging mode: enabled")
    511521
     
    543553!
    544554!-- Generate input file lists
    545     CALL get_input_file_list(                                               &
    546        cfg%start_date, start_hour_flow, end_hour, step_hour,              &
     555    CALL get_input_file_list(                                                  &
     556       cfg%start_date, start_hour_flow, end_hour, step_hour,                   &
    547557       cfg%input_path, flow_prefix, flow_suffix, flow_files)
    548     CALL get_input_file_list(                                               &
    549        cfg%start_date, start_hour_soil, end_hour, step_hour,              &
     558    CALL get_input_file_list(                                                  &
     559       cfg%start_date, start_hour_soil, end_hour, step_hour,                   &
    550560       cfg%input_path, soil_prefix, soil_suffix, soil_files)
    551     CALL get_input_file_list(                                               &
    552        cfg%start_date, start_hour_radiation, end_hour, step_hour,         &
    553        cfg%input_path, radiation_prefix, radiation_suffix, radiation_files, nocheck=.TRUE.)
    554     CALL get_input_file_list(                                               &
    555        cfg%start_date, start_hour_soilmoisture, end_hour_soilmoisture, step_hour, &
    556        cfg%input_path, soilmoisture_prefix, soilmoisture_suffix, soil_moisture_files, nocheck=.TRUE.)
     561    CALL get_input_file_list(                                                  &
     562       cfg%start_date, start_hour_radiation, end_hour, step_hour,              &
     563       cfg%input_path, radiation_prefix, radiation_suffix, radiation_files)
     564    CALL get_input_file_list(                                                  &
     565       cfg%start_date, start_hour_flow, end_hour, step_hour,                  &
     566       cfg%input_path, precipitation_prefix, precipitation_suffix, precip_files )
    557567
    558568!
     
    21372147    INTEGER(iwp) ::  ngroups
    21382148
    2139     ngroups = 16
     2149    ngroups = 17
    21402150    ALLOCATE( io_group_list(ngroups) )
    21412151
     
    22142224!-- rain
    22152225    io_group_list(8) = init_io_group(                                       &
    2216        in_files = soil_moisture_files,                                      &
     2226       in_files = precip_files,                                      &
    22172227       out_vars = output_var_table(33:33),                                  &
    22182228       in_var_list = input_var_table(8:8),                                  &
    2219        kind = 'accumulated'                                                 &
    2220     )
    2221     io_group_list(8)%to_be_processed = .FALSE.
     2229       kind = 'surface'                                                     &
     2230    )
     2231    io_group_list(8)%to_be_processed = cfg%process_precipitation
    22222232!
    22232233!-- snow
    22242234    io_group_list(9) = init_io_group(                                       &
    2225        in_files = soil_moisture_files,                                      &
     2235       in_files = precip_files,                                      &
    22262236       out_vars = output_var_table(34:34),                                  &
    22272237       in_var_list = input_var_table(9:9),                                  &
    2228        kind = 'accumulated'                                                 &
    2229     )
    2230     io_group_list(9)%to_be_processed = .FALSE.
     2238       kind = 'surface'                                                     &
     2239    )
     2240    io_group_list(9)%to_be_processed = cfg%process_precipitation
    22312241!
    22322242!-- graupel
    22332243    io_group_list(10) = init_io_group(                                      &
    2234        in_files = soil_moisture_files,                                      &
     2244       in_files = precip_files,                                      &
    22352245       out_vars = output_var_table(35:35),                                  &
    22362246       in_var_list = input_var_table(10:10),                                &
    2237        kind = 'accumulated'                                                 &
    2238     )
    2239     io_group_list(10)%to_be_processed = .FALSE.
     2247       kind = 'surface'                                                     &
     2248    )
     2249    io_group_list(10)%to_be_processed = cfg%process_precipitation
    22402250!
    22412251!-- evapotranspiration
    22422252    io_group_list(11) = init_io_group(                                      &
    2243        in_files = soil_moisture_files,                                      &
     2253       in_files = precip_files,                                      &
    22442254       out_vars = output_var_table(37:37),                                  &
    22452255       in_var_list = input_var_table(11:11),                                &
     
    22502260!-- 2m air temperature
    22512261    io_group_list(12) = init_io_group(                                      &
    2252        in_files = soil_moisture_files,                                      &
     2262       in_files = precip_files,                                      &
    22532263       out_vars = output_var_table(36:36),                                  &
    22542264       in_var_list = input_var_table(12:12),                                &
     
    22932303    io_group_list(16)%to_be_processed = .FALSE.
    22942304
     2305!-- fog and cloud water
     2306    io_group_list(17) = init_io_group(                                      &
     2307       in_files = flow_files,                                               &
     2308       out_vars = output_var_table(65:94),                                  & !qc, qi, qr, qs, qg
     2309       in_var_list = input_var_table(11:15),                                & !QC, QI, QR, QS, QG
     2310       kind = 'scalar'                                                      &
     2311    )
     2312    io_group_list(17)%to_be_processed = .TRUE.
     2313
     2314    CALL validate_io_groups( io_group_list )
     2315
    22952316 END SUBROUTINE setup_io_groups
     2317
     2318
     2319 SUBROUTINE validate_io_groups( io_group_list )
     2320    TYPE(io_group), TARGET, INTENT(INOUT) ::  io_group_list(:)
     2321
     2322    INTEGER(iwp)                 ::  group_idx, file_idx, outvar_idx
     2323    TYPE(io_group), POINTER      ::  group
     2324    CHARACTER(LEN=PATH), POINTER ::  filename
     2325    TYPE(nc_var), POINTER        ::  outvar, invar
     2326
     2327    DO group_idx = 1, SIZE( io_group_list )
     2328       group => io_group_list(group_idx)
     2329
     2330       IF (group%to_be_processed)  THEN
     2331          DO file_idx = 1, SIZE( group%in_files )
     2332             filename => group%in_files(file_idx)
     2333
     2334             IF (.NOT. file_is_present( filename, 'input', message ))  THEN
     2335                IF (group%is_optional)  THEN
     2336
     2337!--                deactivate group, warn and continue
     2338                   group%to_be_processed = .FALSE.
     2339                   message = "Optional IO group '" // TRIM( group%kind ) // "' was deactivated" // &
     2340                      " because the required file '" // TRIM( filename ) // "' was not found."
     2341                   CALL warn( 'validate_io_groups', message )
     2342                ELSE
     2343!--                abort due to missing input file
     2344                   message = "The input file '" // TRIM( filename ) // "' of the" // &
     2345                      " mandatory IO group '" // TRIM( group%kind ) // "' was not found."
     2346                   CALL inifor_abort( 'validate_io_groups', message  )
     2347                ENDIF
     2348             ELSE
     2349                message = "Set up input file name '" // TRIM(filename) // "'"
     2350                CALL report('verify_file', message)
     2351             ENDIF
     2352
     2353          ENDDO
     2354       
     2355!--       deactivate all optional output variables that have missing inputs
     2356          DO outvar_idx = 1, SIZE(group%out_vars)
     2357             outvar => group%out_vars(outvar_idx)
     2358
     2359             IF (outvar%is_optional)  THEN
     2360
     2361!--             only check first input file, assuming files at later times have the
     2362!--             same contents
     2363                filename => group%in_files(LBOUND( group%in_files, 1))
     2364                invar => group%in_var_list(outvar%input_id)
     2365
     2366!--             if corresponding invar not present, deactivate output_var
     2367                IF ( .NOT.netcdf_variable_present_in_file( invar%name, filename ) )  THEN
     2368                      ! deactivate output variable variable, warn and continue
     2369                      invar%to_be_processed = .FALSE.
     2370                      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 ) // "'."
     2373                      CALL warn( 'validate_io_groups', message )
     2374                ENDIF
     2375             ENDIF
     2376
     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
     2390!--       outvar loop
     2391          ENDDO
     2392
     2393!--   group%to_be_processed conditional
     2394      ENDIF
     2395
     2396!-- groups loop
     2397    ENDDO
     2398   
     2399 END SUBROUTINE validate_io_groups
     2400
    22962401
    22972402
     
    23072412!> on the output quantity Theta.
    23082413!------------------------------------------------------------------------------!
    2309  FUNCTION init_io_group(in_files, out_vars, in_var_list, kind,              &
     2414 FUNCTION init_io_group(in_files, out_vars, in_var_list, kind,                 &
    23102415                        n_output_quantities) RESULT(group)
    23112416    CHARACTER(LEN=PATH), INTENT(IN) ::  in_files(:)
     
    23212426    group%n_inputs = SIZE(in_var_list)
    23222427    group%kind = TRIM(kind)
    2323 !
    2324 !-- For the 'thermodynamics' IO group, one quantity more than input variables
    2325 !-- is needed to compute all output variables of the IO group. Concretely, in
    2326 !-- preprocess() the density is computed from T,P or PP,QV in adddition to
    2327 !-- the variables Theta, p, qv. In read_input_variables(),
    2328 !-- n_output_quantities is used to allocate the correct number of input
    2329 !-- buffers.
    2330     IF ( PRESENT(n_output_quantities) )  THEN
     2428
     2429!
     2430!-- Set the number of output quantities, which is used to allocate input buffers
     2431!-- in the preprocess() routine. For passive scalars, there is a one-to-one
     2432!-- correspondance of input and output quantities. For instance, for every water
     2433!-- phase input variable (e.g. cloud water QC), there is a corresponding output
     2434!-- quantity (qc, which lead to a number of output netCDF variables:
     2435!-- init_atmosphere_qc, ls_forcing_left_qc, etc.)
     2436!--     If more output quantities than input quantities are to be produced,
     2437!-- n_output_quantities can be set through the optional subroutine parameter.
     2438!-- For the 'thermodynamics' IO group, one quantity more than input variables is
     2439!-- needed to compute all output variables of the IO group.  Concretely, in
     2440!-- preprocess() the density is computed from T,P or PP,QV in adddition to the
     2441!-- variables Theta, p, qv. In read_input_variables(), n_output_quantities is
     2442!-- used to allocate the correct number of input buffers.
     2443
     2444    IF  ( PRESENT(n_output_quantities) )  THEN
    23312445       group%n_output_quantities = n_output_quantities
    23322446    ELSE
     
    23932507
    23942508    n_invar = 17
    2395     n_outvar = 64
     2509    n_outvar = 94
    23962510    ALLOCATE( input_var_table(n_invar) )
    23972511    ALLOCATE( output_var_table(n_outvar) )
     
    24612575
    24622576    var => input_var_table(11)
    2463     var%name = 'AEVAP_S'
     2577    var%name = 'QC'
    24642578    var%to_be_processed = .TRUE.
    2465     var%is_upside_down = .FALSE.
     2579    var%is_upside_down = .TRUE.
    24662580
    24672581    var => input_var_table(12)
    2468     var%name = 'T_2M'
     2582    var%name = 'QI'
    24692583    var%to_be_processed = .TRUE.
    2470     var%is_upside_down = .FALSE.
     2584    var%is_upside_down = .TRUE.
    24712585
    24722586    var => input_var_table(13)
    2473     var%name = 'ASWDIFD_S'
     2587    var%name = 'QR'
    24742588    var%to_be_processed = .TRUE.
    2475     var%is_upside_down = .FALSE.
     2589    var%is_upside_down = .TRUE.
    24762590
    24772591    var => input_var_table(14)
    2478     var%name = 'ASWDIR_S'
     2592    var%name = 'QS'
    24792593    var%to_be_processed = .TRUE.
    2480     var%is_upside_down = .FALSE.
     2594    var%is_upside_down = .TRUE.
    24812595
    24822596    var => input_var_table(15)
    2483     var%name = 'ASOB_S'
     2597    var%name = 'QG'
    24842598    var%to_be_processed = .TRUE.
    2485     var%is_upside_down = .FALSE.
     2599    var%is_upside_down = .TRUE.
    24862600
    24872601    var => input_var_table(16)
    2488     var%name = 'ATHB_S'
    2489     var%to_be_processed = .TRUE.
     2602    var%name = '--'
     2603    var%to_be_processed = .FALSE.
    24902604    var%is_upside_down = .FALSE.
    24912605
     
    33323446    output_var_table(64)%averaging_grid => west_averaged_scalar_profile
    33333447    output_var_table(64)%to_be_processed = .NOT. cfg%ug_defined_by_user
     3448
     3449    output_var_table(65) = init_nc_var(                                      &
     3450       name              = 'init_atmosphere_qc',                            &
     3451       std_name          = "",                                              &
     3452       long_name         = "initial cloud water mixture fraction",          &
     3453       units             = "kg/kg",                                         &
     3454       kind              = "init scalar",                                   &
     3455       input_id          = 1_iwp,                                           &
     3456       output_file       = output_file,                                     &
     3457       grid              = palm_grid,                                       &
     3458       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
     3464    output_var_table(65)%is_optional = .TRUE.
     3465
     3466    output_var_table(66) = init_nc_var(                                     &
     3467       name              = 'ls_forcing_left_qc',                            &
     3468       std_name          = "",                                              &
     3469       long_name         = "large-scale forcing for left model boundary for the cloud water mixture fraction", &
     3470       units             = "kg/kg",                                         &
     3471       kind              = "left scalar",                                   &
     3472       input_id          = 1_iwp,                                           &
     3473       output_file       = output_file,                                     &
     3474       grid              = scalars_west_grid,                               &
     3475       intermediate_grid = scalars_west_intermediate                        &
     3476    )
     3477    output_var_table(66)%is_optional = .TRUE.
     3478
     3479    output_var_table(67) = init_nc_var(                                     &
     3480       name              = 'ls_forcing_right_qc',                           &
     3481       std_name          = "",                                              &
     3482       long_name         = "large-scale forcing for right model boundary for the cloud water mixture fraction", &
     3483       units             = "kg/kg",                                         &
     3484       kind              = "right scalar",                                  &
     3485       input_id          = 1_iwp,                                           &
     3486       output_file       = output_file,                                     &
     3487       grid              = scalars_east_grid,                               &
     3488       intermediate_grid = scalars_east_intermediate                        &
     3489    )
     3490    output_var_table(67)%is_optional = .TRUE.
     3491
     3492    output_var_table(68) = init_nc_var(                                     &
     3493       name              = 'ls_forcing_north_qc',                           &
     3494       std_name          = "",                                              &
     3495       long_name         = "large-scale forcing for north model boundary for the cloud water mixture fraction", &
     3496       units             = "kg/kg",                                         &
     3497       kind              = "north scalar",                                  &
     3498       input_id          = 1_iwp,                                           &
     3499       output_file       = output_file,                                     &
     3500       grid              = scalars_north_grid,                              &
     3501       intermediate_grid = scalars_north_intermediate                       &
     3502    )
     3503    output_var_table(68)%is_optional = .TRUE.
     3504
     3505    output_var_table(69) = init_nc_var(                                     &
     3506       name              = 'ls_forcing_south_qc',                           &
     3507       std_name          = "",                                              &
     3508       long_name         = "large-scale forcing for south model boundary for the cloud water mixture fraction", &
     3509       units             = "kg/kg",                                         &
     3510       kind              = "south scalar",                                  &
     3511       input_id          = 1_iwp,                                           &
     3512       output_file       = output_file,                                     &
     3513       grid              = scalars_south_grid,                              &
     3514       intermediate_grid = scalars_south_intermediate                       &
     3515    )
     3516    output_var_table(69)%is_optional = .TRUE.
     3517
     3518    output_var_table(70) = init_nc_var(                                     &
     3519       name              = 'ls_forcing_top_qc',                             &
     3520       std_name          = "",                                              &
     3521       long_name         = "large-scale forcing for top model boundary for the cloud water mixture fraction", &
     3522       units             = "kg/kg",                                         &
     3523       kind              = "top scalar",                                    &
     3524       input_id          = 1_iwp,                                           &
     3525       output_file       = output_file,                                     &
     3526       grid              = scalars_top_grid,                                &
     3527       intermediate_grid = scalars_top_intermediate                         &
     3528    )
     3529    output_var_table(70)%is_optional = .TRUE.
     3530
     3531    output_var_table(71) = init_nc_var(                                     &
     3532       name              = 'init_atmosphere_qi',                            &
     3533       std_name          = "",                                              &
     3534       long_name         = "initial cloud ice mixture fraction",            &
     3535       units             = "kg/kg",                                         &
     3536       kind              = "init scalar",                                   &
     3537       input_id          = 2_iwp,                                           &
     3538       output_file       = output_file,                                     &
     3539       grid              = palm_grid,                                       &
     3540       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
     3546    output_var_table(71)%is_optional = .TRUE.
     3547
     3548    output_var_table(72) = init_nc_var(                                     &
     3549       name              = 'ls_forcing_left_qi',                            &
     3550       std_name          = "",                                              &
     3551       long_name         = "large-scale forcing for left model boundary for the cloud ice mixture fraction", &
     3552       units             = "kg/kg",                                         &
     3553       kind              = "left scalar",                                   &
     3554       input_id          = 2_iwp,                                           &
     3555       output_file       = output_file,                                     &
     3556       grid              = scalars_west_grid,                               &
     3557       intermediate_grid = scalars_west_intermediate                        &
     3558    )
     3559    output_var_table(72)%is_optional = .TRUE.
     3560
     3561    output_var_table(73) = init_nc_var(                                     &
     3562       name              = 'ls_forcing_right_qi',                           &
     3563       std_name          = "",                                              &
     3564       long_name         = "large-scale forcing for right model boundary for the cloud ice mixture fraction", &
     3565       units             = "kg/kg",                                         &
     3566       kind              = "right scalar",                                  &
     3567       input_id          = 2_iwp,                                           &
     3568       output_file       = output_file,                                     &
     3569       grid              = scalars_east_grid,                               &
     3570       intermediate_grid = scalars_east_intermediate                        &
     3571    )
     3572    output_var_table(73)%is_optional = .TRUE.
     3573
     3574    output_var_table(74) = init_nc_var(                                     &
     3575       name              = 'ls_forcing_north_qi',                           &
     3576       std_name          = "",                                              &
     3577       long_name         = "large-scale forcing for north model boundary for the cloud ice mixture fraction", &
     3578       units             = "kg/kg",                                         &
     3579       kind              = "north scalar",                                  &
     3580       input_id          = 2_iwp,                                           &
     3581       output_file       = output_file,                                     &
     3582       grid              = scalars_north_grid,                              &
     3583       intermediate_grid = scalars_north_intermediate                       &
     3584    )
     3585    output_var_table(74)%is_optional = .TRUE.
     3586
     3587    output_var_table(75) = init_nc_var(                                     &
     3588       name              = 'ls_forcing_south_qi',                           &
     3589       std_name          = "",                                              &
     3590       long_name         = "large-scale forcing for south model boundary for the cloud ice mixture fraction", &
     3591       units             = "kg/kg",                                         &
     3592       kind              = "south scalar",                                  &
     3593       input_id          = 2_iwp,                                           &
     3594       output_file       = output_file,                                     &
     3595       grid              = scalars_south_grid,                              &
     3596       intermediate_grid = scalars_south_intermediate                       &
     3597    )
     3598    output_var_table(75)%is_optional = .TRUE.
     3599
     3600    output_var_table(76) = init_nc_var(                                     &
     3601       name              = 'ls_forcing_top_qi',                             &
     3602       std_name          = "",                                              &
     3603       long_name         = "large-scale forcing for top model boundary for the cloud ice mixture fraction", &
     3604       units             = "kg/kg",                                         &
     3605       kind              = "top scalar",                                    &
     3606       input_id          = 2_iwp,                                           &
     3607       output_file       = output_file,                                     &
     3608       grid              = scalars_top_grid,                                &
     3609       intermediate_grid = scalars_top_intermediate                         &
     3610    )
     3611    output_var_table(76)%is_optional = .TRUE.
     3612
     3613    output_var_table(77) = init_nc_var(                                     &
     3614       name              = 'init_atmosphere_qr',                            &
     3615       std_name          = "",                                              &
     3616       long_name         = "initial rain water mixture fraction",            &
     3617       units             = "kg/kg",                                         &
     3618       kind              = "init scalar",                                   &
     3619       input_id          = 3_iwp,                                           &
     3620       output_file       = output_file,                                     &
     3621       grid              = palm_grid,                                       &
     3622       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
     3628    output_var_table(77)%is_optional = .TRUE.
     3629
     3630    output_var_table(78) = init_nc_var(                                     &
     3631       name              = 'ls_forcing_left_qr',                            &
     3632       std_name          = "",                                              &
     3633       long_name         = "large-scale forcing for left model boundary for the rain water mixture fraction", &
     3634       units             = "kg/kg",                                         &
     3635       kind              = "left scalar",                                   &
     3636       input_id          = 3_iwp,                                           &
     3637       output_file       = output_file,                                     &
     3638       grid              = scalars_west_grid,                               &
     3639       intermediate_grid = scalars_west_intermediate                        &
     3640    )
     3641    output_var_table(78)%is_optional = .TRUE.
     3642
     3643    output_var_table(79) = init_nc_var(                                     &
     3644       name              = 'ls_forcing_right_qr',                           &
     3645       std_name          = "",                                              &
     3646       long_name         = "large-scale forcing for right model boundary for the rain water mixture fraction", &
     3647       units             = "kg/kg",                                         &
     3648       kind              = "right scalar",                                  &
     3649       input_id          = 3_iwp,                                           &
     3650       output_file       = output_file,                                     &
     3651       grid              = scalars_east_grid,                               &
     3652       intermediate_grid = scalars_east_intermediate                        &
     3653    )
     3654    output_var_table(79)%is_optional = .TRUE.
     3655
     3656    output_var_table(80) = init_nc_var(                                     &
     3657       name              = 'ls_forcing_north_qr',                           &
     3658       std_name          = "",                                              &
     3659       long_name         = "large-scale forcing for north model boundary for the rain water mixture fraction", &
     3660       units             = "kg/kg",                                         &
     3661       kind              = "north scalar",                                  &
     3662       input_id          = 3_iwp,                                           &
     3663       output_file       = output_file,                                     &
     3664       grid              = scalars_north_grid,                              &
     3665       intermediate_grid = scalars_north_intermediate                       &
     3666    )
     3667    output_var_table(80)%is_optional = .TRUE.
     3668
     3669    output_var_table(81) = init_nc_var(                                     &
     3670       name              = 'ls_forcing_south_qr',                           &
     3671       std_name          = "",                                              &
     3672       long_name         = "large-scale forcing for south model boundary for the rain water mixture fraction", &
     3673       units             = "kg/kg",                                         &
     3674       kind              = "south scalar",                                  &
     3675       input_id          = 3_iwp,                                           &
     3676       output_file       = output_file,                                     &
     3677       grid              = scalars_south_grid,                              &
     3678       intermediate_grid = scalars_south_intermediate                       &
     3679    )
     3680    output_var_table(81)%is_optional = .TRUE.
     3681
     3682    output_var_table(82) = init_nc_var(                                     &
     3683       name              = 'ls_forcing_top_qr',                             &
     3684       std_name          = "",                                              &
     3685       long_name         = "large-scale forcing for top model boundary for the rain water mixture fraction", &
     3686       units             = "kg/kg",                                         &
     3687       kind              = "top scalar",                                    &
     3688       input_id          = 3_iwp,                                           &
     3689       output_file       = output_file,                                     &
     3690       grid              = scalars_top_grid,                                &
     3691       intermediate_grid = scalars_top_intermediate                         &
     3692    )
     3693    output_var_table(82)%is_optional = .TRUE.
     3694
     3695    output_var_table(83) = init_nc_var(                                     &
     3696       name              = 'init_atmosphere_qs',                            &
     3697       std_name          = "",                                              &
     3698       long_name         = "initial snow mixture fraction",            &
     3699       units             = "kg/kg",                                         &
     3700       kind              = "init scalar",                                   &
     3701       input_id          = 4_iwp,                                           &
     3702       output_file       = output_file,                                     &
     3703       grid              = palm_grid,                                       &
     3704       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
     3710    output_var_table(83)%is_optional = .TRUE.
     3711
     3712    output_var_table(84) = init_nc_var(                                     &
     3713       name              = 'ls_forcing_left_qs',                            &
     3714       std_name          = "",                                              &
     3715       long_name         = "large-scale forcing for left model boundary for the snow mixture fraction", &
     3716       units             = "kg/kg",                                         &
     3717       kind              = "left scalar",                                   &
     3718       input_id          = 4_iwp,                                           &
     3719       output_file       = output_file,                                     &
     3720       grid              = scalars_west_grid,                               &
     3721       intermediate_grid = scalars_west_intermediate                        &
     3722    )
     3723    output_var_table(84)%is_optional = .TRUE.
     3724
     3725    output_var_table(85) = init_nc_var(                                     &
     3726       name              = 'ls_forcing_right_qs',                           &
     3727       std_name          = "",                                              &
     3728       long_name         = "large-scale forcing for right model boundary for the snow mixture fraction", &
     3729       units             = "kg/kg",                                         &
     3730       kind              = "right scalar",                                  &
     3731       input_id          = 4_iwp,                                           &
     3732       output_file       = output_file,                                     &
     3733       grid              = scalars_east_grid,                               &
     3734       intermediate_grid = scalars_east_intermediate                        &
     3735    )
     3736    output_var_table(85)%is_optional = .TRUE.
     3737
     3738    output_var_table(86) = init_nc_var(                                     &
     3739       name              = 'ls_forcing_north_qs',                           &
     3740       std_name          = "",                                              &
     3741       long_name         = "large-scale forcing for north model boundary for the snow mixture fraction", &
     3742       units             = "kg/kg",                                         &
     3743       kind              = "north scalar",                                  &
     3744       input_id          = 4_iwp,                                           &
     3745       output_file       = output_file,                                     &
     3746       grid              = scalars_north_grid,                              &
     3747       intermediate_grid = scalars_north_intermediate                       &
     3748    )
     3749    output_var_table(86)%is_optional = .TRUE.
     3750
     3751    output_var_table(87) = init_nc_var(                                     &
     3752       name              = 'ls_forcing_south_qs',                           &
     3753       std_name          = "",                                              &
     3754       long_name         = "large-scale forcing for south model boundary for the snow mixture fraction", &
     3755       units             = "kg/kg",                                         &
     3756       kind              = "south scalar",                                  &
     3757       input_id          = 4_iwp,                                           &
     3758       output_file       = output_file,                                     &
     3759       grid              = scalars_south_grid,                              &
     3760       intermediate_grid = scalars_south_intermediate                       &
     3761    )
     3762    output_var_table(87)%is_optional = .TRUE.
     3763
     3764    output_var_table(88) = init_nc_var(                                     &
     3765       name              = 'ls_forcing_top_qs',                             &
     3766       std_name          = "",                                              &
     3767       long_name         = "large-scale forcing for top model boundary for the snow mixture fraction", &
     3768       units             = "kg/kg",                                         &
     3769       kind              = "top scalar",                                    &
     3770       input_id          = 4_iwp,                                           &
     3771       output_file       = output_file,                                     &
     3772       grid              = scalars_top_grid,                                &
     3773       intermediate_grid = scalars_top_intermediate                         &
     3774    )
     3775    output_var_table(88)%is_optional = .TRUE.
     3776
     3777    output_var_table(89) = init_nc_var(                                     &
     3778       name              = 'init_atmosphere_qg',                            &
     3779       std_name          = "",                                              &
     3780       long_name         = "initial graupel mixture fraction",            &
     3781       units             = "kg/kg",                                         &
     3782       kind              = "init scalar",                                   &
     3783       input_id          = 5_iwp,                                           &
     3784       output_file       = output_file,                                     &
     3785       grid              = palm_grid,                                       &
     3786       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
     3792    output_var_table(89)%is_optional = .TRUE.
     3793
     3794    output_var_table(90) = init_nc_var(                                     &
     3795       name              = 'ls_forcing_left_qg',                            &
     3796       std_name          = "",                                              &
     3797       long_name         = "large-scale forcing for left model boundary for the graupel mixture fraction", &
     3798       units             = "kg/kg",                                         &
     3799       kind              = "left scalar",                                   &
     3800       input_id          = 5_iwp,                                           &
     3801       output_file       = output_file,                                     &
     3802       grid              = scalars_west_grid,                               &
     3803       intermediate_grid = scalars_west_intermediate                        &
     3804    )
     3805    output_var_table(90)%is_optional = .TRUE.
     3806
     3807    output_var_table(91) = init_nc_var(                                     &
     3808       name              = 'ls_forcing_right_qg',                           &
     3809       std_name          = "",                                              &
     3810       long_name         = "large-scale forcing for right model boundary for the graupel mixture fraction", &
     3811       units             = "kg/kg",                                         &
     3812       kind              = "right scalar",                                  &
     3813       input_id          = 5_iwp,                                           &
     3814       output_file       = output_file,                                     &
     3815       grid              = scalars_east_grid,                               &
     3816       intermediate_grid = scalars_east_intermediate                        &
     3817    )
     3818    output_var_table(91)%is_optional = .TRUE.
     3819
     3820    output_var_table(92) = init_nc_var(                                     &
     3821       name              = 'ls_forcing_north_qg',                           &
     3822       std_name          = "",                                              &
     3823       long_name         = "large-scale forcing for north model boundary for the graupel mixture fraction", &
     3824       units             = "kg/kg",                                         &
     3825       kind              = "north scalar",                                  &
     3826       input_id          = 5_iwp,                                           &
     3827       output_file       = output_file,                                     &
     3828       grid              = scalars_north_grid,                              &
     3829       intermediate_grid = scalars_north_intermediate                       &
     3830    )
     3831    output_var_table(92)%is_optional = .TRUE.
     3832
     3833    output_var_table(93) = init_nc_var(                                     &
     3834       name              = 'ls_forcing_south_qg',                           &
     3835       std_name          = "",                                              &
     3836       long_name         = "large-scale forcing for south model boundary for the graupel mixture fraction", &
     3837       units             = "kg/kg",                                         &
     3838       kind              = "south scalar",                                  &
     3839       input_id          = 5_iwp,                                           &
     3840       output_file       = output_file,                                     &
     3841       grid              = scalars_south_grid,                              &
     3842       intermediate_grid = scalars_south_intermediate                       &
     3843    )
     3844    output_var_table(93)%is_optional = .TRUE.
     3845
     3846    output_var_table(94) = init_nc_var(                                     &
     3847       name              = 'ls_forcing_top_qg',                             &
     3848       std_name          = "",                                              &
     3849       long_name         = "large-scale forcing for top model boundary for the graupel mixture fraction", &
     3850       units             = "kg/kg",                                         &
     3851       kind              = "top scalar",                                    &
     3852       input_id          = 5_iwp,                                           &
     3853       output_file       = output_file,                                     &
     3854       grid              = scalars_top_grid,                                &
     3855       intermediate_grid = scalars_top_intermediate                         &
     3856    )
     3857    output_var_table(94)%is_optional = .TRUE.
    33343858
    33353859!
     
    37114235   
    37124236    CALL report('fini_file_lists', 'Deallocating file lists', cfg%debug)
    3713     DEALLOCATE( flow_files, soil_files, radiation_files, soil_moisture_files )
     4237    DEALLOCATE( flow_files, soil_files, radiation_files, precip_files )
    37144238
    37154239 END SUBROUTINE fini_file_lists
     
    37274251!> array will match a COSMO-DE scalar array.
    37284252!------------------------------------------------------------------------------!
    3729  SUBROUTINE preprocess(group, input_buffer, cosmo_grid, iter)
     4253 SUBROUTINE preprocess( group, input_buffer, cosmo_grid )
    37304254
    37314255    TYPE(io_group), INTENT(INOUT), TARGET       ::  group
    37324256    TYPE(container), INTENT(INOUT), ALLOCATABLE ::  input_buffer(:)
    37334257    TYPE(grid_definition), INTENT(IN)           ::  cosmo_grid
    3734     INTEGER(iwp), INTENT(IN)                    ::  iter
    37354258   
    37364259    REAL(wp), ALLOCATABLE                       ::  basic_state_pressure(:)
    37374260    TYPE(container), ALLOCATABLE                ::  preprocess_buffer(:)
    3738     INTEGER(iwp)                                ::  hour, dt
    37394261    INTEGER(iwp)                                ::  i, j, k
    37404262    INTEGER(iwp)                                ::  nx, ny, nz
     
    39354457          input_buffer(:)%is_preprocessed = .TRUE.
    39364458
    3937        CASE( 'accumulated' ) !
    3938           message = "De-accumulating '" // TRIM(group%in_var_list(1)%name) //&
    3939                     "' in iteration " // TRIM(str(iter))
    3940           CALL report('preprocess', message)
    3941 
    3942           hour = iter - 1_iwp
    3943           dt = MODULO(hour, 3_iwp) + 1_iwp ! averaging period
    3944           SELECT CASE(dt)
    3945 
    3946 !
    3947 !--          input has been accumulated over one hour. Leave as is
    3948 !--          input_buffer(1)%array(:,:,:) carrries one-hour integral
    3949              CASE(1)
    3950              
    3951 !           
    3952 !--          input has been accumulated over two hours. Subtract previous step
    3953 !--          input_buffer(1)%array(:,:,:) carrries one-hour integral
    3954 !--          input_buffer(2)%array(:,:,:) carrries two-hour integral
    3955              CASE(2)
    3956                 CALL deaverage(                                                   &
    3957                          avg_1 = input_buffer(1)%array(:,:,:), t1 = 1.0_wp,     &
    3958                          avg_2 = input_buffer(2)%array(:,:,:), t2 = 1.0_wp,     &
    3959                          avg_3 = input_buffer(1)%array(:,:,:), t3 = 1.0_wp )
    3960 !           
    3961 !--             input_buffer(1)%array(:,:,:) carrries one-hour integral of second hour
    3962              
    3963 !           
    3964 !--          input has been accumulated over three hours. Subtract previous step
    3965 !--          input_buffer(1)%array(:,:,:) carrries three-hour integral
    3966 !--          input_buffer(2)%array(:,:,:) still carrries two-hour integral
    3967              CASE(3)
    3968                 CALL deaverage(                                                   &
    3969                         avg_1 = input_buffer(2)%array(:,:,:), t1 = 1.0_wp,      &
    3970                         avg_2 = input_buffer(1)%array(:,:,:), t2 = 1.0_wp,      &
    3971                         avg_3 = input_buffer(1)%array(:,:,:), t3 = 1.0_wp )
    3972 !           
    3973 !--             input_buffer(1)%array(:,:,:) carrries one-hour integral of third hourA
    3974              
    3975              CASE DEFAULT
    3976                 message = "Invalid averaging period '" // TRIM(str(dt)) // " hours"
    3977                 message = "Invalid averaging period '" // TRIM(str(dt)) // " hours"
    3978                 CALL inifor_abort('preprocess', message)
    3979 
    3980           END SELECT
    3981           input_buffer(:)%is_preprocessed = .TRUE.
    3982 
    3983        CASE( 'running average' ) !
    3984           message = "De-averaging '" // TRIM(group%in_var_list(1)%name) //   &
    3985                     "' in iteration " // TRIM(str(iter))
    3986           CALL report('preprocess', message)
    3987 
    3988           hour = iter - 1_iwp
    3989 !
    3990 !--       averaging period
    3991           dt = MODULO(hour, 3_iwp) + 1_iwp
    3992           SELECT CASE(dt)
    3993 !
    3994 !--          input has been accumulated over one hour. Leave as is
    3995 !--          input_buffer(1)%array(:,:,:) carrries one-hour integral
    3996              CASE(1)
    3997              
    3998 !           
    3999 !--          input has been accumulated over two hours. Subtract previous step
    4000 !--          input_buffer(1)%array(:,:,:) carrries one-hour integral
    4001 !--          input_buffer(2)%array(:,:,:) carrries two-hour integral
    4002              CASE(2)
    4003                 CALL deaverage( input_buffer(1)%array(:,:,:), 1.0_wp,           &
    4004                                 input_buffer(2)%array(:,:,:), 2.0_wp,           &
    4005                                 input_buffer(1)%array(:,:,:), 1.0_wp)
    4006 !           
    4007 !--             input_buffer(1)%array(:,:,:) carrries one-hour integral of second hour
    4008              
    4009 !           
    4010 !--          input has been accumulated over three hours. Subtract previous step
    4011 !--          input_buffer(1)%array(:,:,:) carrries three-hour integral
    4012 !--          input_buffer(2)%array(:,:,:) still carrries two-hour integral
    4013              CASE(3)
    4014                 CALL deaverage( input_buffer(2)%array(:,:,:), 2.0_wp,           &
    4015                                 input_buffer(1)%array(:,:,:), 3.0_wp,           &
    4016                                 input_buffer(1)%array(:,:,:), 1.0_wp)
    4017 !           
    4018 !--             input_buffer(1)%array(:,:,:) carrries one-hour integral of third hourA
    4019              
    4020              CASE DEFAULT
    4021                 message = "Invalid averaging period '" // TRIM(str(dt)) // " hours"
    4022                 CALL inifor_abort('preprocess', message)
    4023 
    4024           END SELECT
    4025           input_buffer(:)%is_preprocessed = .TRUE.
    4026 
    40274459       CASE DEFAULT
    40284460          message = "IO group kind '" // TRIM(group%kind) // "' is not supported."
Note: See TracChangeset for help on using the changeset viewer.