Ignore:
Timestamp:
Sep 10, 2019 5:03:24 PM (5 years ago)
Author:
suehring
Message:

Offline nesting: data input modularized; time variable is defined relative to time_utc_init, so that input data is correctly mapped to actual model time; checks rephrased and new checks for the time dimension added; Netcdf input: routine to retrieve dimension length renamed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/virtual_measurement_mod.f90

    r4182 r4226  
    2525! -----------------
    2626! $Id$
     27! Netcdf input routine for dimension length renamed
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    435438 
    436439    USE netcdf_data_input_mod,                                                 &
    437         ONLY:  init_model, input_file_vm,                                      &
    438                netcdf_data_input_get_dimension_length,                         &
    439                netcdf_data_input_att, netcdf_data_input_var
     440        ONLY:  get_dimension_length,                                           &
     441               init_model,                                                     &
     442               input_file_vm,                                                  &
     443               netcdf_data_input_att,                                          &
     444               netcdf_data_input_var
    440445       
    441446    IMPLICIT NONE
     
    648653!--          For non-stationary measurements read the number of trajectories
    649654!--          and the number of time coordinates.
    650              CALL netcdf_data_input_get_dimension_length( vmea_general%id_vm, &
    651                                                           vmea(l)%ntraj,      &
    652                                                           "traj" //           &
    653                                                           TRIM( dum ) )
    654              CALL netcdf_data_input_get_dimension_length( vmea_general%id_vm, &
    655                                                           dim_ntime,          &
    656                                                           "ntime" //          &
    657                                                           TRIM( dum ) )
     655             CALL get_dimension_length( vmea_general%id_vm,                    &
     656                                        vmea(l)%ntraj,                         &
     657                                        "traj" //                              &
     658                                        TRIM( dum ) )
     659             CALL get_dimension_length( vmea_general%id_vm,                    &
     660                                        dim_ntime,                             &
     661                                        "ntime" //                             &
     662                                        TRIM( dum ) )
    658663!
    659664!--       For stationary measurements the dimension for UTM and time
Note: See TracChangeset for help on using the changeset viewer.