Ignore:
Timestamp:
Apr 5, 2019 9:01:56 AM (5 years ago)
Author:
monakurppa
Message:

major changes in salsa: data input, format and performance

  • Time-dependent emissions enabled: lod=1 for yearly PM emissions that are normalised depending on the time, and lod=2 for preprocessed emissions (similar to the chemistry module).
  • Additionally, 'uniform' emissions allowed. This emission is set constant on all horisontal upward facing surfaces and it is created based on parameters surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
  • All emissions are now implemented as surface fluxes! No 3D sources anymore.
  • Update the emission information by calling salsa_emission_update if skip_time_do_salsa >= time_since_reference_point and next_aero_emission_update <= time_since_reference_point
  • Aerosol background concentrations read from PIDS_DYNAMIC. The vertical grid must match the one applied in the model.
  • Gas emissions and background concentrations can be also read in in salsa_mod if the chemistry module is not applied.
  • In deposition, information on the land use type can be now imported from the land use model
  • Use SI units in PARIN, i.e. n_lognorm given in #/m3 and dpg in metres.
  • Apply 100 character line limit
  • Change all variable names from capital to lowercase letter
  • Change real exponents to integer if possible. If not, precalculate the value of exponent
  • Rename in1a to start_subrange_1a, fn2a to end_subrange_1a etc.
  • Rename nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and ngast --> ngases_salsa
  • Rename ibc to index_bc, idu to index_du etc.
  • Renamed loop indices b, c and sg to ib, ic and ig
  • run_salsa subroutine removed
  • Corrected a bud in salsa_driver: falsely applied ino instead of inh
  • Call salsa_tendency within salsa_prognostic_equations which is called in module_interface_mod instead of prognostic_equations_mod
  • Removed tailing white spaces and unused variables
  • Change error message to start by PA instead of SA
File:
1 edited

Legend:

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

    r3855 r3864  
    2525! -----------------
    2626! $Id$
     27! get_variable_4d_to_3d_real modified to enable read in data of type
     28! data(t,y,x,n) one timestep at a time + some routines made public
     29!
     30! 3855 2019-04-03 10:00:59Z suehring
    2731! Typo removed
    2832!
     
    913917           netcdf_data_input_interpolate, netcdf_data_input_offline_nesting,   &
    914918           netcdf_data_input_surface_data, netcdf_data_input_topo,             &
    915            netcdf_data_input_var, get_attribute, get_variable, open_read_file
     919           netcdf_data_input_var, get_attribute, get_variable, open_read_file, &
     920           check_existence, inquire_num_variables, inquire_variable_names
    916921
    917922
     
    55575562       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
    55585563       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
    5559        
     5564
    55605565       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
    55615566                                                                 !< to its reverse memory access
     
    55665571!
    55675572!--    Inquire variable id
    5568        nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )   
     5573       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    55695574!
    55705575!--    Check for collective read-operation and set respective NetCDF flags if
     
    55735578#if defined( __netcdf4_parallel )
    55745579          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
    5575 #endif         
     5580#endif
    55765581       ENDIF
    55775582!
     
    55825587       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
    55835588                               start = (/ is+1,    js+1,    ks+1 /),           &
    5584                                count = (/ ie-is+1, je-js+1, ke-ks+1 /) )                             
    5585 
    5586        CALL handle_error( 'get_variable_3d_int8', 533, variable_name )                               
     5589                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )
     5590
     5591       CALL handle_error( 'get_variable_3d_int8', 533, variable_name )
    55875592!
    55885593!--    Resort data. Please note, dimension subscripts of var all start at 1.
     
    55945599          ENDDO
    55955600       ENDDO
    5596        
     5601
    55975602       DEALLOCATE( tmp )
    55985603
     
    56275632       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
    56285633       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
    5629        
     5634
    56305635       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
    56315636                                                         !< to its reverse memory access
     
    56415646!--    required.
    56425647       IF ( collective_read )  THEN
    5643 #if defined( __netcdf4_parallel )       
     5648#if defined( __netcdf4_parallel )
    56445649          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
    56455650#endif
     
    56535658                               start = (/ is+1,    js+1,    ks+1 /),           &
    56545659                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )   
    5655                                
     5660
    56565661       CALL handle_error( 'get_variable_3d_real', 534, variable_name )
    56575662!
     
    56645669          ENDDO
    56655670       ENDDO
    5666        
     5671
    56675672       DEALLOCATE( tmp )
    56685673
     
    57375742       ELSE
    57385743!
    5739 !--    Allocate temporary variable according to memory access on file.
    5740        ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
    5741 !
    5742 !--    Get variable
    5743           nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
     5744!--       Allocate temporary variable according to memory access on file.
     5745          ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
     5746!
     5747!--       Get variable
     5748          nc_stat = NF90_GET_VAR( id, id_var, tmp,                             &
    57445749                               start = (/ is+1,    js+1,   k1s+1, k2s+1 /),    &
    57455750                               count = (/ ie-is+1, je-js+1,                    &
     
    57485753          CALL handle_error( 'get_variable_4d_real', 535, variable_name )
    57495754!
    5750 !--    Resort data. Please note, dimension subscripts of var all start at 1.
     5755!--       Resort data. Please note, dimension subscripts of var all start at 1.
    57515756          DO  i = is, ie
    57525757             DO  j = js, je
     
    57585763             ENDDO
    57595764          ENDDO
    5760        
     5765
    57615766          DEALLOCATE( tmp )
    57625767       ENDIF
     
    58285833       ELSE
    58295834!
    5830 !--    Allocate temporary variable according to memory access on file.
     5835!--       Allocate temporary variable according to memory access on file.
    58315836          ALLOCATE( tmp(is:ie,js:je,ks:ke) )
    58325837!
    5833 !--    Get variable
    5834           nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
    5835                                   start = (/ ns+1, is+1,    js+1,    ks+1 /),           &
    5836                                   count = (/ 1, ie-is+1, je-js+1, ke-ks+1 /) )   
    5837                                
     5838!--       Get variable
     5839          nc_stat = NF90_GET_VAR( id, id_var, tmp,                             &
     5840                                  start = (/ is+1,    js+1,    ks+1,   ns+1 /),&
     5841                                  count = (/ ie-is+1, je-js+1, ke-ks+1, 1   /) )
     5842
    58385843          CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name )
    58395844!
    5840 !--    Resort data. Please note, dimension subscripts of var all start at 1.
    5841           DO  i = is, ie 
     5845!--       Resort data. Please note, dimension subscripts of var all start at 1.
     5846          DO  i = is, ie
    58425847             DO  j = js, je
    58435848                DO  k = ks, ke
     
    58465851             ENDDO
    58475852          ENDDO
    5848        
     5853
    58495854         DEALLOCATE( tmp )
    58505855
     
    59625967       CHARACTER(LEN=*)              ::  variable_name   !< variable name
    59635968
    5964        INTEGER(iwp)                  ::  ns              !< start index for subdomain input along n dimension: ns coincides here with ne, since, we select only one value along the 1st dimension n
     5969       INTEGER(iwp)                  ::  ns              !< start index for subdomain input along n dimension:
     5970                                                         !< ns coincides here with ne, since, we select only one
     5971                                                         !< value along the 1st dimension n
    59655972
    59665973       INTEGER(iwp)                  ::  t               !< index along t direction
     
    59865993!
    59875994!--    Inquire variable id
    5988        nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 
     5995       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    59895996!
    59905997!--    Check for collective read-operation and set respective NetCDF flags if
    5991 !--    required. 
     5998!--    required.
    59925999       IF ( collective_read )  THEN
    59936000          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     
    60366043          ENDDO
    60376044
    6038          DEALLOCATE( tmp )
     6045          DEALLOCATE( tmp )
    60396046
    60406047       ENDIF
Note: See TracChangeset for help on using the changeset viewer.