Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

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

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Introduced new PALM grid stretching
     24! Renamend initial-condition mode variable 'mode' to 'ic_mode'
     25! Improved log messages
    2326!
    2427!
     
    4851        ONLY:  setup_parameters, setup_grids, setup_variable_tables,           &
    4952               setup_io_groups, fini_grids, fini_variables, fini_io_groups,    &
    50                fini_file_lists, preprocess,                                    &
     53               fini_file_lists, preprocess, origin_lon, origin_lat,            &
    5154               output_file, io_group_list, output_var_table,                   &
    52                cosmo_grid, palm_grid, nx, ny, nz, ug, vg, p0, mode,            &
    53                imin, imax, jmin, jmax
     55               cosmo_grid, palm_grid, nx, ny, nz, ug, vg, p0, cfg,             &
     56               average_imin, average_imax, average_jmin, average_jmax
    5457
    5558    USE io
     
    8487
    8588    ! Initialize the netCDF output file and define dimensions
    86     CALL setup_netcdf_dimensions(output_file, palm_grid)
     89    CALL setup_netcdf_dimensions(output_file, palm_grid, cfg % start_date,    &
     90                                 origin_lon, origin_lat)
    8791 CALL run_control('time', 'write')
    8892
    8993    ! Set up the tables containing the input and output variables and set
    9094    ! the corresponding netCDF dimensions for each output variable
    91     CALL setup_variable_tables(mode)
     95    CALL setup_variable_tables(cfg % ic_mode)
    9296 CALL run_control('time', 'write')
    9397
     
    9599    CALL setup_netcdf_variables(output_file % name, output_var_table)
    96100
    97     CALL setup_io_groups() 
     101    CALL setup_io_groups()
    98102 CALL run_control('time', 'init')
    99103
     
    118122 CALL run_control('time', 'comp')
    119123
     124             !TODO: move this assertion into 'preprocess'.
    120125             IF ( .NOT. ALL(input_buffer(:) % is_preprocessed .AND. .TRUE.) )  THEN
    121126                message = "Input buffers for group '" // TRIM(group % kind) // &
     
    159164                      CASE DEFAULT
    160165
    161                           CALL abort("main loop", 'Not a soil variable')
     166                          message = "'" // TRIM(output_var % kind) // "' is not a soil variable"
     167                          CALL abort("main loop", message)
    162168
    163169                      END SELECT
     
    173179                      ALLOCATE( output_arr( 0:output_var % grid % nx,          &
    174180                                            0:output_var % grid % ny,          &
    175                                             0:output_var % grid % nz ) )
     181                                            1:output_var % grid % nz ) )
    176182
    177183 CALL run_control('time', 'alloc')
     
    187193                      ALLOCATE( output_arr( 0:output_var % grid % nx,          &
    188194                                            0:output_var % grid % ny,          &
    189                                             0:output_var % grid % nz ) )
     195                                            1:output_var % grid % nz ) )
    190196 CALL run_control('time', 'alloc')
    191197                     
     
    193199                      CALL average_profile(                                    &
    194200                         input_buffer(output_var % input_id) % array(:,:,:),   &
    195                          output_arr(:,:,:), imin, imax, jmin, jmax,            &
     201                         output_arr(:,:,:), average_imin, average_imax,        &
     202                         average_jmin, average_jmax,                           &
    196203                         output_var % intermediate_grid,                       &
    197204                         output_var % grid)
     
    205212 CALL run_control('time', 'comp')
    206213
    207                    CASE ( 'profile' )
     214                   CASE ( 'set profile' )
    208215                     
    209                       ALLOCATE( output_arr( 1, 1, 0:nz ) )
     216                      ALLOCATE( output_arr( 1, 1, 1:nz ) )
    210217 CALL run_control('time', 'alloc')
    211218
     
    217224                      CASE('ls_forcing_vg')
    218225                          output_arr(1, 1, :) = vg
     226
     227                      CASE('nudging_tau')
     228                          output_arr(1, 1, :) = NUDGING_TAU
    219229
    220230                      CASE DEFAULT
     
    225235                      END SELECT
    226236 CALL run_control('time', 'comp')
     237
     238                   CASE('average large-scale profile')
     239                      message = "Averaging of large-scale forcing profiles " //&
     240                                "has not been implemented, yet."
     241                      CALL abort('main loop', message)
     242                      !ALLOCATE( output_arr( 1, 1, 1:nz ) )
    227243
    228244                   CASE DEFAULT
     
    269285       ELSE
    270286
    271           message = "Skipping IO group '" // TRIM(group % kind) // "'"
     287          message = "Skipping IO group " // TRIM(str(igroup)) // " '" // TRIM(group % kind) // "'"
    272288          IF ( ALLOCATED(group % in_var_list) )  THEN
    273289              message = TRIM(message) // " with input variable '" //           &
     
    291307 CALL run_control('report', 'void')
    292308
    293     message = "Finished writing forcing file '" // TRIM(output_file % name) // &
     309    message = "Finished writing dynamic driver '" // TRIM(output_file % name) // &
    294310              "' successfully."
    295311    CALL report('main loop', message)
Note: See TracChangeset for help on using the changeset viewer.