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/salsa_util_mod.f90

    r3655 r3864  
    2525! -----------------
    2626! $Id$
     27! Formatting changes
     28!
     29! 3845 2019-04-01 13:41:55Z monakurppa
    2730! Initial revision
    28 ! 
    29 ! 
     31!
     32!
    3033!
    3134! Authors:
     
    3942!------------------------------------------------------------------------------!
    4043 MODULE salsa_util_mod
    41  
     44
     45    USE control_parameters,                                                                        &
     46        ONLY:  message_string
     47
    4248    USE kinds
    43    
     49
    4450    USE pegrid
    45    
     51
    4652    IMPLICIT NONE
    47    
    48     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l !< subdomain sum
    49                                         !< of vertical passive salsa flux w's'
    50                                         !< (5th-order advection scheme only)
    5153
     54    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l !< subdomain sum of vertical salsa
     55                                                              !< flux w's' (5th-order advection
     56                                                              !< scheme only)
     57!
    5258!-- Component index
    5359    TYPE component_index
    54        INTEGER(iwp) ::  ncomp !< Number of components
    55        INTEGER(iwp), ALLOCATABLE ::  ind(:) !< Component index
    56        CHARACTER(len=3), ALLOCATABLE ::  comp(:) !< Component name
    57     END TYPE component_index 
    58    
     60       INTEGER(iwp) ::  ncomp  !< Number of components
     61       INTEGER(iwp), ALLOCATABLE ::  ind(:)  !< Component index
     62       CHARACTER(len=3), ALLOCATABLE ::  comp(:)  !< Component name
     63    END TYPE component_index
     64
    5965    SAVE
    60    
     66
    6167    INTERFACE component_index_constructor
    6268       MODULE PROCEDURE component_index_constructor
    6369    END INTERFACE component_index_constructor
    64    
     70
    6571    INTERFACE get_index
    6672       MODULE PROCEDURE get_index
    6773    END INTERFACE get_index
    68    
    69     INTERFACE get_n_comp
    70        MODULE PROCEDURE get_n_comp
    71     END INTERFACE get_n_comp
    72    
     74
    7375    INTERFACE is_used
    7476       MODULE PROCEDURE is_used
    7577    END INTERFACE is_used
    76    
     78
    7779    PRIVATE
    78     PUBLIC component_index, component_index_constructor, get_index, get_n_comp,&
    79            is_used, sums_salsa_ws_l
    80    
     80    PUBLIC component_index, component_index_constructor, get_index, is_used, sums_salsa_ws_l
     81
    8182 CONTAINS
    82    
    83 !------------------------------------------------------------------------------!   
     83
     84!------------------------------------------------------------------------------!
    8485! Description:
    8586! ------------
    8687!> Creates index tables for different (aerosol) components
    8788!------------------------------------------------------------------------------!
    88     SUBROUTINE component_index_constructor( SELF, ncomp, nlist, listcomp )
     89    SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
    8990
    9091       IMPLICIT NONE
    91        
    92        TYPE(component_index), INTENT(inout) ::  SELF !< Object containing the indices
    93                                                      !< of different aerosol components
    94        INTEGER(iwp), INTENT(inout) ::  ncomp !< Number of components
    95        INTEGER(iwp), INTENT(in) ::     nlist !< Maximum number of components
    96        CHARACTER(len=3), INTENT(in) ::  listcomp(nlist) !< List cof component
    97                                                         !< names
    98        INTEGER(iwp) ::  i, jj
    99        
     92
     93       INTEGER(iwp) ::  i   !<
     94       INTEGER(iwp) ::  jj  !<
     95
     96       INTEGER(iwp), INTENT(in) ::  nlist ! < Maximum number of components
     97
     98       INTEGER(iwp), INTENT(inout) ::  ncomp  !< Number of components
     99
     100       TYPE(component_index), INTENT(inout) ::  self  !< Object containing the indices of different
     101                                                      !< aerosol components
     102       CHARACTER(len=3), INTENT(in) ::  listcomp(nlist)  !< List cof component names
     103
    100104       ncomp = 0
    101        
    102        DO  WHILE ( listcomp(ncomp+1) /= '  ' .AND. ncomp < nlist )
     105
     106       DO WHILE ( listcomp(ncomp+1) /= '  ' .AND. ncomp < nlist )
    103107          ncomp = ncomp + 1
    104108       ENDDO
    105        
    106        SELF%ncomp = ncomp
    107        ALLOCATE( SELF%ind(ncomp), SELF%comp(ncomp) )
    108        
    109        DO i = 1, ncomp
    110           SELF%ind(i) = i
     109
     110       self%ncomp = ncomp
     111       ALLOCATE( self%ind(ncomp), self%comp(ncomp) )
     112
     113       DO  i = 1, ncomp
     114          self%ind(i) = i
    111115       ENDDO
    112        
     116
    113117       jj = 1
    114        DO i = 1, nlist
     118       DO  i = 1, nlist
    115119          IF ( listcomp(i) == '') CYCLE
    116           SELF%comp(jj) = listcomp(i)
    117           jj = jj+1
     120          self%comp(jj) = listcomp(i)
     121          jj = jj + 1
    118122       ENDDO
    119        
     123
    120124    END SUBROUTINE component_index_constructor
    121125
     
    125129!> Gives the index of a component in the component list
    126130!------------------------------------------------------------------------------!
    127     INTEGER FUNCTION get_index( SELF, incomp )
     131    INTEGER FUNCTION get_index( self, incomp )
    128132
    129133       IMPLICIT NONE
    130        
    131        TYPE(component_index), INTENT(in) ::  SELF !< Object containing the
    132                                                   !< indices of different
    133                                                   !< aerosol components
     134
    134135       CHARACTER(len=*), INTENT(in) ::  incomp !< Component name
    135136       INTEGER(iwp) ::  i
    136        
    137        IF ( ANY(SELF%comp == incomp) ) THEN
     137
     138       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
     139                                                   !< aerosol components
     140       IF ( ANY( self%comp == incomp ) ) THEN
    138141          i = 1
    139           DO WHILE ( (SELF%comp(i) /= incomp) )
    140              i = i+1
     142          DO WHILE ( (self%comp(i) /= incomp) )
     143             i = i + 1
    141144          ENDDO
    142145          get_index = i
    143146       ELSEIF ( incomp == 'H2O' ) THEN
    144           get_index = SELF%ncomp + 1
     147          get_index = self%ncomp + 1
    145148       ELSE
    146           STOP 1 ! "INFO for Developer: please use the message routine to pass the output string" get_index: FAILED, no such component -
     149          WRITE( message_string, * ) 'Incorrect component name given!'
     150          CALL message( 'get_index', 'PA0591', 1, 2, 0, 6, 0 )
    147151       ENDIF
    148        
     152
    149153       RETURN
    150        
     154
    151155    END FUNCTION get_index
    152 
    153 !------------------------------------------------------------------------------!
    154 ! Description:
    155 ! ------------
    156 !> Get the number of (aerosol) components used
    157 !------------------------------------------------------------------------------!
    158     INTEGER FUNCTION get_n_comp( SELF )
    159 
    160        IMPLICIT NONE
    161 
    162        TYPE(component_index), INTENT(in) ::  SELF !< Object containing the
    163                                                   !< indices of different
    164                                                   !< aerosol components
    165        get_n_comp = SELF%ncomp
    166        RETURN
    167        
    168     END FUNCTION
    169156
    170157!------------------------------------------------------------------------------!
     
    173160!> Tells if the (aerosol) component is being used in the simulation
    174161!------------------------------------------------------------------------------!
    175     LOGICAL FUNCTION is_used( SELF, icomp )
     162    LOGICAL FUNCTION is_used( self, icomp )
    176163
    177164       IMPLICIT NONE
    178        
    179        TYPE(component_index), INTENT(in) ::  SELF !< Object containing the
    180                                                   !< indices of different
    181                                                   !< aerosol components
     165
    182166       CHARACTER(len=*), INTENT(in) ::  icomp !< Component name
    183        
    184        IF ( ANY(SELF%comp == icomp) ) THEN
     167
     168       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
     169                                                   !< aerosol components
     170
     171       IF ( ANY(self%comp == icomp) ) THEN
    185172          is_used = .TRUE.
    186173       ELSE
    187174          is_used = .FALSE.
    188175       ENDIF
    189        
    190        RETURN
    191        
     176
    192177    END FUNCTION
    193178
Note: See TracChangeset for help on using the changeset viewer.