Ignore:
Timestamp:
Jul 7, 2016 10:43:48 AM (8 years ago)
Author:
suehring
Message:

flight module added

File:
1 edited

Legend:

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

    r1851 r1957  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! flight module added
    2222!
    2323! Former revisions:
     
    139139 MODULE netcdf_interface
    140140
    141     USE control_parameters, ONLY: max_masks
     141    USE control_parameters, ONLY: max_masks, fl_max, var_fl_max
    142142    USE kinds
    143143#if defined( __netcdf )
     
    238238    CHARACTER(LEN=40) ::  netcdf_data_format_string
    239239
    240     INTEGER(iwp) ::  id_dim_prtnum, id_dim_time_pr, id_dim_time_prt, &
     240    INTEGER(iwp) ::  id_dim_prtnum, id_dim_time_fl, id_dim_time_pr, id_dim_time_prt, &
    241241                     id_dim_time_pts, id_dim_time_sp, id_dim_time_ts, id_dim_x_sp, &
    242                      id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp, id_set_pr, &
    243                      id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_var_prtnum, &
    244                      id_var_rnop_prt, id_var_time_pr, id_var_time_prt, &
     242                     id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp, id_set_fl, id_set_pr, &
     243                     id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_var_time_fl, &
     244                     id_var_prtnum, id_var_rnop_prt, id_var_time_pr, id_var_time_prt, &
    245245                     id_var_time_pts, id_var_time_sp, id_var_time_ts, id_var_x_sp, &
    246246                     id_var_y_sp, id_var_zu_sp, id_var_zw_sp, nc_stat
     247
    247248
    248249    INTEGER(iwp), DIMENSION(0:1) ::  id_dim_time_xy, id_dim_time_xz, &
     
    271272                                        !< compression
    272273
     274    INTEGER(iwp)                 ::  dofl_time_count
    273275    INTEGER(iwp), DIMENSION(10)  ::  id_var_dospx, id_var_dospy
    274276    INTEGER(iwp), DIMENSION(20)  ::  id_var_prt
    275277    INTEGER(iwp), DIMENSION(11)  ::  nc_precision
    276278    INTEGER(iwp), DIMENSION(dopr_norm_num) ::  id_var_norm_dopr
     279   
     280    INTEGER(iwp), DIMENSION(fl_max) ::  id_dim_x_fl, id_dim_y_fl, id_dim_z_fl
     281    INTEGER(iwp), DIMENSION(fl_max) ::  id_var_x_fl, id_var_y_fl, id_var_z_fl
     282   
     283    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_label
     284    CHARACTER (LEN=20), DIMENSION(fl_max*var_fl_max) :: dofl_unit
     285    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_x
     286    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_y
     287    CHARACTER (LEN=20), DIMENSION(fl_max) :: dofl_dim_label_z
     288
     289    INTEGER(iwp), DIMENSION(fl_max*var_fl_max) :: id_var_dofl   
    277290
    278291    INTEGER(iwp), DIMENSION(dopts_num,0:10) ::  id_var_dopts
     
    300313
    301314
    302     PUBLIC  domask_unit, dopr_unit, dopts_num, dots_label, dots_max, dots_num, &
    303             dots_rad, dots_soil, dots_unit, do2d_unit, do3d_unit, id_set_mask, &
    304             id_set_pr, id_set_prt, id_set_pts, id_set_sp, id_set_ts,           &
    305             id_set_xy, id_set_xz, id_set_yz, id_set_3d, id_var_domask,         &
    306             id_var_dopr, id_var_dopts, id_var_dospx, id_var_dospy,             &
    307             id_var_dots, id_var_do2d, id_var_do3d, id_var_norm_dopr,           &
    308             id_var_time_mask, id_var_time_pr, id_var_time_pts, id_var_time_sp, &
    309             id_var_time_ts, id_var_time_xy, id_var_time_xz, id_var_time_yz,    &
    310             id_var_time_3d, nc_stat, netcdf_data_format,                       &
    311             netcdf_data_format_string, netcdf_deflate, netcdf_precision,       &
    312             output_for_t0
    313 
     315    PUBLIC  dofl_dim_label_x, dofl_dim_label_y, dofl_dim_label_z, dofl_label,  &
     316            dofl_time_count, dofl_unit, domask_unit, dopr_unit, dopts_num,     &
     317            dots_label, dots_max, dots_num, dots_rad, dots_soil, dots_unit,    &
     318            do2d_unit, do3d_unit, id_set_fl, id_set_mask, id_set_pr,           &
     319            id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_set_xy, id_set_xz,&
     320            id_set_yz, id_set_3d, id_var_domask, id_var_dofl, id_var_dopr,     &
     321            id_var_dopts, id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d,&
     322            id_var_do3d, id_var_norm_dopr, id_var_time_fl, id_var_time_mask,   &
     323            id_var_time_pr, id_var_time_pts, id_var_time_sp, id_var_time_ts,   &
     324            id_var_time_xy, id_var_time_xz, id_var_time_yz, id_var_time_3d,    &
     325            id_var_x_fl, id_var_y_fl, id_var_z_fl,  nc_stat,                   &
     326            netcdf_data_format, netcdf_data_format_string, netcdf_deflate,     &
     327            netcdf_precision, output_for_t0
     328           
     329           
    314330    SAVE
    315331
     
    366382               simulated_time_at_begin, skip_time_data_output_av,              &
    367383               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
    368                skip_time_do3d, topography
     384               skip_time_do3d, topography, num_leg, num_var_fl
    369385
    370386    USE grid_variables,                                                        &
     
    433449    INTEGER(iwp) ::  ntime_count                             !< number of time levels found in file
    434450    INTEGER(iwp) ::  nz_old                                  !<
     451    INTEGER(iwp) ::  l                                       !<
    435452
    436453    INTEGER(iwp), SAVE ::  oldmode                           !<
     
    510527             CASE ( 'masks' )
    511528                nc_precision(11) = j
     529             CASE ( 'fl' )
     530                nc_precision(9) = j
    512531             CASE ( 'all' )
    513532                nc_precision    = j
     
    48874906          CALL message( 'netcdf_define_header', 'PA0269', 0, 0, 0, 6, 0 )
    48884907
    4889 
     4908!
     4909!--    Flight data
     4910       CASE ( 'fl_new' )
     4911!
     4912!--       Define some global attributes of the dataset
     4913          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
     4914                                  TRIM( run_description_header ) )
     4915          CALL netcdf_handle_error( 'netcdf_define_header', 249 )
     4916
     4917!
     4918!--       Define time and location coordinates for flight space-time series
     4919!--       (unlimited dimension)
     4920!--       Error number must still be set appropriately.
     4921          CALL netcdf_create_dim( id_set_fl, 'time', NF90_UNLIMITED,           &
     4922                                  id_dim_time_fl, 250 )
     4923          CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /), 'time',     &
     4924                                  NF90_DOUBLE, id_var_time_fl, 'seconds', '',  &
     4925                                  251, 252, 000 )
     4926
     4927          DO l = 1, num_leg
     4928             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_x(l),           &
     4929                                     NF90_UNLIMITED, id_dim_x_fl(l), 250 )
     4930             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_y(l),           &
     4931                                     NF90_UNLIMITED, id_dim_y_fl(l), 250 )
     4932             CALL netcdf_create_dim( id_set_fl, dofl_dim_label_z(l),           &
     4933                                     NF90_UNLIMITED, id_dim_z_fl(l), 250 )
     4934
     4935             CALL netcdf_create_var( id_set_fl, (/ id_dim_x_fl(l) /),          &
     4936                                     dofl_dim_label_x(l), NF90_DOUBLE,         &
     4937                                     id_var_x_fl(l), 'm', '', 251, 252, 000 )
     4938             CALL netcdf_create_var( id_set_fl, (/ id_dim_y_fl(l) /),          &
     4939                                     dofl_dim_label_y(l), NF90_DOUBLE,         &
     4940                                     id_var_y_fl(l), 'm', '', 251, 252, 000 )
     4941             CALL netcdf_create_var( id_set_fl, (/ id_dim_z_fl(l) /),          &
     4942                                     dofl_dim_label_z(l), NF90_DOUBLE,         &
     4943                                     id_var_z_fl(l), 'm', '', 251, 252, 000 )
     4944          ENDDO
     4945!
     4946!--       Define the variables
     4947          var_list = ';'
     4948          k = 1
     4949          DO  l = 1, num_leg
     4950             DO i = 1, num_var_fl
     4951
     4952                CALL netcdf_create_var( id_set_fl, (/ id_dim_time_fl /),       &
     4953                                        dofl_label(k), nc_precision(9),        &
     4954                                        id_var_dofl(k),                        &
     4955                                        TRIM( dofl_unit(k) ),                  &
     4956                                        TRIM( dofl_label(k) ), 253, 254, 255 )
     4957
     4958                k = k + 1
     4959               
     4960             ENDDO
     4961
     4962          ENDDO
     4963
     4964!
     4965!--       Write the list of variables as global attribute (this is used by
     4966!--       restart runs)
     4967          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST', var_list )
     4968          CALL netcdf_handle_error( 'netcdf_define_header', 258 )
     4969
     4970!
     4971!--       Leave netCDF define mode
     4972          nc_stat = NF90_ENDDEF( id_set_fl )
     4973          CALL netcdf_handle_error( 'netcdf_define_header', 259 )
     4974
     4975
     4976       CASE ( 'fl_ext' )
     4977
     4978!
     4979!--       Get the list of variables and compare with the actual run.
     4980!--       First var_list_old has to be reset, since GET_ATT does not assign
     4981!--       trailing blanks.
     4982          var_list_old = ' '
     4983          nc_stat = NF90_GET_ATT( id_set_fl, NF90_GLOBAL, 'VAR_LIST',          &
     4984                                  var_list_old )
     4985          CALL netcdf_handle_error( 'netcdf_define_header', 260 )
     4986
     4987          var_list = ';'
     4988          i = 1
     4989          DO  i = 1, num_leg * num_var_fl
     4990
     4991             var_list = TRIM( var_list ) // TRIM( dofl_label(i) ) // ';'
     4992
     4993          ENDDO
     4994
     4995          IF ( TRIM( var_list ) /= TRIM( var_list_old ) )  THEN
     4996             message_string = 'netCDF file for flight time series ' //         &
     4997                              'from previous run found,' //                    &
     4998                              '& but this file cannot be extended due to' //   &
     4999                              ' variable mismatch.' //                         &
     5000                              '&New file is created instead.'
     5001             CALL message( 'define_netcdf_header', 'PA0257', 0, 1, 0, 6, 0 )
     5002             extend = .FALSE.
     5003             RETURN
     5004          ENDIF
     5005
     5006!
     5007!--       Get the id of the time coordinate (unlimited coordinate) and its
     5008!--       last index on the file. The next time level is dofl_time_count+1.
     5009!--       The current time must be larger than the last output time
     5010!--       on the file.
     5011          nc_stat = NF90_INQ_VARID( id_set_fl, 'time', id_var_time_fl )
     5012          CALL netcdf_handle_error( 'netcdf_define_header', 261 )
     5013
     5014          nc_stat = NF90_INQUIRE_VARIABLE( id_set_fl, id_var_time_fl, &
     5015                                           dimids = id_dim_time_old )
     5016          CALL netcdf_handle_error( 'netcdf_define_header', 262 )
     5017          id_dim_time_fl = id_dim_time_old(1)
     5018
     5019          nc_stat = NF90_INQUIRE_DIMENSION( id_set_fl, id_dim_time_fl, &
     5020                                            len = dofl_time_count )
     5021          CALL netcdf_handle_error( 'netcdf_define_header', 263 )
     5022
     5023          nc_stat = NF90_GET_VAR( id_set_fl, id_var_time_fl,        &
     5024                                  last_time_coordinate,             &
     5025                                  start = (/ dofl_time_count /), &
     5026                                  count = (/ 1 /) )
     5027          CALL netcdf_handle_error( 'netcdf_define_header', 264 )
     5028
     5029          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     5030             message_string = 'netCDF file for flight-time series ' //      &
     5031                              'from previous run found,' //                 &
     5032                              '&but this file cannot be extended becaus' // &
     5033                              'e the current output time' //                &
     5034                              '&is less or equal than the last output t' // &
     5035                              'ime on this file.' //                        &
     5036                              '&New file is created instead.'
     5037             CALL message( 'define_netcdf_header', 'PA0258', 0, 1, 0, 6, 0 )
     5038             dofl_time_count = 0
     5039             extend = .FALSE.
     5040             RETURN
     5041          ENDIF
     5042
     5043!
     5044!--       Dataset seems to be extendable.
     5045!--       Now get the remaining dimension and variable ids
     5046          DO l = 1, num_leg
     5047             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_x(l),         &
     5048                                       id_var_x_fl(l) )
     5049             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
     5050             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_y(l),         &
     5051                                       id_var_y_fl(l) )
     5052             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
     5053             nc_stat = NF90_INQ_VARID( id_set_fl, dofl_dim_label_z(l),         &
     5054                                       id_var_z_fl(l) )
     5055             CALL netcdf_handle_error( 'netcdf_define_header', 265 )
     5056
     5057          ENDDO
     5058
     5059
     5060          DO  i = 1, num_leg * num_var_fl
     5061 
     5062            nc_stat = NF90_INQ_VARID( id_set_fl, dofl_label(i), &
     5063                                       id_var_dofl(i) )
     5064            CALL netcdf_handle_error( 'netcdf_define_header', 265 )
     5065
     5066          ENDDO
     5067
     5068!
     5069!--       Update the title attribute on file
     5070!--       In order to avoid 'data mode' errors if updated attributes are larger
     5071!--       than their original size, NF90_PUT_ATT is called in 'define mode'
     5072!--       enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a possible
     5073!--       performance loss due to data copying; an alternative strategy would be
     5074!--       to ensure equal attribute size in a job chain. Maybe revise later.
     5075          nc_stat = NF90_REDEF( id_set_fl )
     5076          CALL netcdf_handle_error( 'netcdf_define_header', 439 )
     5077          nc_stat = NF90_PUT_ATT( id_set_fl, NF90_GLOBAL, 'title',             &
     5078                                  TRIM( run_description_header ) )
     5079          CALL netcdf_handle_error( 'netcdf_define_header', 267 )
     5080          nc_stat = NF90_ENDDEF( id_set_fl )
     5081          CALL netcdf_handle_error( 'netcdf_define_header', 440 )
     5082          message_string = 'netCDF file for flight-time series ' //            &
     5083                           'from previous run found.' //                       &
     5084                           '&This file will be extended.'
     5085          CALL message( 'define_netcdf_header', 'PA0259', 0, 0, 0, 6, 0 )
     5086
     5087         
    48905088       CASE DEFAULT
    48915089
Note: See TracChangeset for help on using the changeset viewer.