Ignore:
Timestamp:
Jul 20, 2018 11:20:01 AM (6 years ago)
Author:
sward
Message:

Added multi agent system

File:
1 edited

Legend:

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

    r3049 r3159  
    2525! -----------------
    2626! $Id$
     27! Added multi agent system
     28!
     29! 3049 2018-05-29 13:52:36Z Giersch
    2730! Error messages revised
    2831!
     
    282285    PRIVATE
    283286
     287    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_names =                      &
     288          (/ 'ag_x            ', 'ag_y            ', 'ag_wind         ',       &
     289             'ag_temp         ', 'ag_group        ', 'PM10            ',       &
     290             'PM25            ', 'ag_therm_comf   ', 'ag_uv           ',       &
     291             'not_used        ', 'not_used        ', 'not_used        ',       &
     292             'not_used        ' /)
     293
     294    CHARACTER (LEN=16), DIMENSION(13) ::  agt_var_units = &
     295          (/ 'meters          ', 'meters          ', 'm/s             ',       &
     296             'K               ', 'dim_less        ', 'tbd             ',       &
     297             'tbd             ', 'tbd             ', 'tbd             ',       &
     298             'not_used        ', 'not_used        ', 'not_used        ',       &
     299             'not_used        ' /)
     300
    284301    INTEGER(iwp), PARAMETER ::  dopr_norm_num = 7, dopts_num = 29, dots_max = 100
    285302
     
    377394    CHARACTER(LEN=40) ::  netcdf_data_format_string
    378395
    379     INTEGER(iwp) ::  id_dim_prtnum, id_dim_time_fl, id_dim_time_pr, id_dim_time_prt, &
    380                      id_dim_time_pts, id_dim_time_sp, id_dim_time_ts, id_dim_x_sp, &
    381                      id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp, id_set_fl, id_set_pr, &
    382                      id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_var_time_fl, &
    383                      id_var_prtnum, id_var_rnop_prt, id_var_time_pr, id_var_time_prt, &
    384                      id_var_time_pts, id_var_time_sp, id_var_time_ts, id_var_x_sp, &
    385                      id_var_y_sp, id_var_zu_sp, id_var_zw_sp, nc_stat
     396    INTEGER(iwp) ::  id_dim_agtnum, id_dim_prtnum, id_dim_time_agt,            &
     397                     id_dim_time_fl, id_dim_time_pr, id_dim_time_prt,          &
     398                     id_dim_time_pts, id_dim_time_sp, id_dim_time_ts,          &
     399                     id_dim_x_sp, id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp,     &
     400                     id_set_agt, id_set_fl, id_set_pr, id_set_prt, id_set_pts, &
     401                     id_set_sp, id_set_ts, id_var_agtnum, id_var_time_agt,     &
     402                     id_var_time_fl, id_var_prtnum, id_var_rnoa_agt,           &
     403                     id_var_rnop_prt, id_var_time_pr, id_var_time_prt,         &
     404                     id_var_time_pts, id_var_time_sp, id_var_time_ts,          &
     405                     id_var_x_sp, id_var_y_sp, id_var_zu_sp, id_var_zw_sp,     &
     406                     nc_stat
    386407
    387408
     
    413434    INTEGER(iwp)                 ::  dofl_time_count
    414435    INTEGER(iwp), DIMENSION(10)  ::  id_var_dospx, id_var_dospy
     436    INTEGER(iwp), DIMENSION(20)  ::  id_var_agt
    415437    INTEGER(iwp), DIMENSION(20)  ::  id_var_prt
    416438    INTEGER(iwp), DIMENSION(11)  ::  nc_precision
     
    457479            dofl_time_count, dofl_unit, domask_unit, dopr_unit, dopts_num,     &
    458480            dots_label, dots_max, dots_num, dots_rad, dots_soil, dots_unit,    &
    459             do2d_unit, do3d_unit, fill_value,                                  &
    460             id_set_fl, id_set_mask, id_set_pr,                                 &
    461             id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_set_xy, id_set_xz,&
    462             id_set_yz, id_set_3d, id_var_domask, id_var_dofl, id_var_dopr,     &
    463             id_var_dopts, id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d,&
    464             id_var_do3d, id_var_norm_dopr, id_var_time_fl, id_var_time_mask,   &
    465             id_var_time_pr, id_var_time_pts, id_var_time_sp, id_var_time_ts,   &
     481            do2d_unit, do3d_unit, fill_value, id_set_agt, id_set_fl,           &
     482            id_set_mask, id_set_pr, id_set_prt, id_set_pts, id_set_sp,         &
     483            id_set_ts, id_set_xy, id_set_xz, id_set_yz, id_set_3d, id_var_agt, &
     484            id_var_domask, id_var_dofl, id_var_dopr, id_var_dopts,             &
     485            id_var_dospx, id_var_dospy, id_var_dots, id_var_do2d, id_var_do3d, &
     486            id_var_norm_dopr, id_var_time_agt, id_var_time_fl,                 &
     487            id_var_time_mask, id_var_time_pr, id_var_rnoa_agt, id_var_time_pts,&
     488            id_var_time_sp, id_var_time_ts,                                    &
    466489            id_var_time_xy, id_var_time_xz, id_var_time_yz, id_var_time_3d,    &
    467490            id_var_x_fl, id_var_y_fl, id_var_z_fl,  nc_stat,                   &
     
    515538
    516539    USE control_parameters,                                                    &
    517         ONLY:  air_chemistry, averaging_interval, averaging_interval_pr,       &
    518                data_output_pr, domask, dopr_n,                                 &
     540        ONLY:  agent_time_unlimited, air_chemistry, averaging_interval,        &
     541               averaging_interval_pr, data_output_pr, domask, dopr_n,          &
    519542               dopr_time_count, dopts_time_count, dots_time_count,             &
    520543               do2d, do2d_at_begin, do2d_xz_time_count, do3d, do3d_at_begin,   &
    521544               do2d_yz_time_count, dt_data_output_av, dt_do2d_xy, dt_do2d_xz,  &
    522                dt_do2d_yz, dt_do3d, mask_size, do2d_xy_time_count,             &
     545               dt_do2d_yz, dt_do3d, dt_write_agent_data, mask_size,            &
     546               do2d_xy_time_count,                                             &
    523547               do3d_time_count, domask_time_count, end_time, land_surface,     &
    524548               mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global,      &
     
    19221946                           '&This file will be extended.'
    19231947          CALL message( 'define_netcdf_header', 'PA0248', 0, 0, 0, 6, 0 )
     1948
     1949
     1950       CASE ( 'ag_new' )
     1951
     1952!
     1953!--       Define some global attributes of the dataset
     1954          nc_stat = NF90_PUT_ATT( id_set_agt, NF90_GLOBAL, 'title', &
     1955                                  TRIM( run_description_header ) )
     1956          CALL netcdf_handle_error( 'netcdf_define_header', 330 )
     1957!
     1958!--       Switch for unlimited time dimension
     1959          IF ( agent_time_unlimited ) THEN
     1960             CALL netcdf_create_dim( id_set_agt, 'time', NF90_UNLIMITED,       &
     1961                                     id_dim_time_agt, 331 )
     1962          ELSE
     1963             CALL netcdf_create_dim( id_set_agt, 'time',                       &
     1964                                     INT(end_time/dt_write_agent_data*1.2),    &
     1965                                     id_dim_time_agt, 331 )
     1966          ENDIF
     1967
     1968          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /), 'time',   &
     1969                                  NF90_DOUBLE, id_var_time_agt, 'seconds', '', &
     1970                                  332, 333, 000 )
     1971!
     1972!--       netCDF4 allows more than one unlimited dimension
     1973          CALL netcdf_create_dim( id_set_agt, 'agent_number',            &
     1974                                  NF90_UNLIMITED, id_dim_agtnum, 334 )
     1975
     1976          CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum /),             &
     1977                                  'agent_number', NF90_DOUBLE,              &
     1978                                  id_var_agtnum, 'agent number', '', 335,   &
     1979                                  336, 000 )
     1980!
     1981!--       Define variable which contains the real number of agents in use
     1982          CALL netcdf_create_var( id_set_agt, (/ id_dim_time_agt /),           &
     1983                                  'real_num_of_agt', NF90_DOUBLE,              &
     1984                                  id_var_rnoa_agt, 'agent number', '', 337, &
     1985                                  338, 000 )
     1986!
     1987!--       Define the variables
     1988          DO  i = 1, 5
     1989             CALL netcdf_create_var( id_set_agt, (/ id_dim_agtnum,             &
     1990                                     id_dim_time_agt /), agt_var_names(i),     &
     1991                                     nc_precision(8), id_var_agt(i),           &
     1992                                     TRIM( agt_var_units(i) ),                 &
     1993                                     TRIM( agt_var_names(i) ), 339, 340, 341 )
     1994
     1995          ENDDO
     1996!
     1997!--       Leave netCDF define mode
     1998          nc_stat = NF90_ENDDEF( id_set_agt )
     1999          CALL netcdf_handle_error( 'netcdf_define_header', 342 )
     2000
     2001
     2002!        CASE ( 'ag_ext' )
     2003! !+?agent extend output for restart runs has to be adapted
     2004!
     2005! !
     2006! !--       Get the id of the time coordinate (unlimited coordinate) and its
     2007! !--       last index on the file. The next time level is prt..count+1.
     2008! !--       The current time must be larger than the last output time
     2009! !--       on the file.
     2010!           nc_stat = NF90_INQ_VARID( id_set_agt, 'time', id_var_time_agt )
     2011!           CALL netcdf_handle_error( 'netcdf_define_header', 343 )
     2012!
     2013!           nc_stat = NF90_INQUIRE_VARIABLE( id_set_agt, id_var_time_agt, &
     2014!                                            dimids = id_dim_time_old )
     2015!           CALL netcdf_handle_error( 'netcdf_define_header', 344 )
     2016!           id_dim_time_agt = id_dim_time_old(1)
     2017!
     2018!           nc_stat = NF90_INQUIRE_DIMENSION( id_set_agt, id_dim_time_agt, &
     2019!                                             len = agt_time_count )
     2020!           CALL netcdf_handle_error( 'netcdf_define_header', 345 )
     2021!
     2022!           nc_stat = NF90_GET_VAR( id_set_agt, id_var_time_agt,  &
     2023!                                   last_time_coordinate,         &
     2024!                                   start = (/ agt_time_count /), &
     2025!                                   count = (/ 1 /) )
     2026!           CALL netcdf_handle_error( 'netcdf_define_header', 346 )
     2027!
     2028!           IF ( last_time_coordinate(1) >= simulated_time )  THEN
     2029!              message_string = 'netCDF file for agents ' //                  &
     2030!                               'from previous run found,' //                 &
     2031!                               '&but this file cannot be extended becaus' // &
     2032!                               'e the current output time' //                &
     2033!                               '&is less or equal than the last output t' // &
     2034!                               'ime on this file.' //                        &
     2035!                               '&New file is created instead.'
     2036!              CALL message( 'define_netcdf_header', 'PA0265', 0, 1, 0, 6, 0 )
     2037!              agt_time_count = 0
     2038!              extend = .FALSE.
     2039!              RETURN
     2040!           ENDIF
     2041!
     2042! !
     2043! !--       Dataset seems to be extendable.
     2044! !--       Now get the variable ids.
     2045!           nc_stat = NF90_INQ_VARID( id_set_agt, 'real_num_of_agt', &
     2046!                                     id_var_rnoa_agt )
     2047!           CALL netcdf_handle_error( 'netcdf_define_header', 347 )
     2048!
     2049!           DO  i = 1, 17
     2050!
     2051!              nc_stat = NF90_INQ_VARID( id_set_agt, agt_var_names(i), &
     2052!                                        id_var_prt(i) )
     2053!              CALL netcdf_handle_error( 'netcdf_define_header', 348 )
     2054!
     2055!           ENDDO
     2056!
     2057!           message_string = 'netCDF file for particles ' // &
     2058!                            'from previous run found.' //   &
     2059!                            '&This file will be extended.'
     2060!           CALL message( 'define_netcdf_header', 'PA0266', 0, 0, 0, 6, 0 )
     2061         
    19242062
    19252063       CASE ( 'xy_new' )
Note: See TracChangeset for help on using the changeset viewer.