Ignore:
Timestamp:
Oct 17, 2019 11:29:38 AM (4 years ago)
Author:
schwenkel
Message:

Introducing module interface for boundary conditions and move module specific boundary conditions into their modules

File:
1 edited

Legend:

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

    r4256 r4268  
    2626! -----------------
    2727! $Id$
     28! Moving module specific boundary conditions from time_integration to module
     29!
     30! 4256 2019-10-07 10:08:52Z monakurppa
    2831! Document previous changes: use global variables nx, ny and nz in salsa_header
    2932!
     
    773776    END INTERFACE salsa_boundary_conds
    774777
     778    INTERFACE salsa_boundary_conditions
     779       MODULE PROCEDURE salsa_boundary_conditions
     780    END INTERFACE salsa_boundary_conditions
     781
    775782    INTERFACE salsa_check_data_output
    776783       MODULE PROCEDURE salsa_check_data_output
     
    866873!
    867874!-- Public functions:
    868     PUBLIC salsa_boundary_conds, salsa_check_data_output, salsa_check_parameters,                 &
     875    PUBLIC salsa_boundary_conds, salsa_check_data_output, salsa_check_parameters, salsa_boundary_conditions, &
    869876           salsa_3d_data_averaging, salsa_data_output_2d, salsa_data_output_3d,                    &
    870877           salsa_data_output_mask, salsa_define_netcdf_grid, salsa_diagnostics, salsa_driver,      &
     
    79547961 END SUBROUTINE salsa_tendency
    79557962
     7963
     7964!------------------------------------------------------------------------------!
     7965! Description:
     7966! ------------
     7967!> Boundary conditions for prognostic variables in SALSA from module interface
     7968!------------------------------------------------------------------------------!
     7969 SUBROUTINE salsa_boundary_conditions
     7970
     7971    IMPLICIT NONE
     7972
     7973    INTEGER(iwp) ::  ib              !< index for aerosol size bins
     7974    INTEGER(iwp) ::  ic              !< index for aerosol mass bins
     7975    INTEGER(iwp) ::  icc             !< additional index for aerosol mass bins
     7976    INTEGER(iwp) ::  ig              !< index for salsa gases
     7977
     7978!
     7979!-- Boundary conditions for prognostic quantitites of other modules:
     7980!-- Here, only decycling is carried out
     7981    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     7982
     7983       DO  ib = 1, nbins_aerosol
     7984          CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
     7985          DO  ic = 1, ncomponents_mass
     7986             icc = ( ic - 1 ) * nbins_aerosol + ib
     7987             CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
     7988          ENDDO
     7989       ENDDO
     7990       IF ( .NOT. salsa_gases_from_chem )  THEN
     7991          DO  ig = 1, ngases_salsa
     7992             CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
     7993          ENDDO
     7994       ENDIF
     7995
     7996    ENDIF
     7997
     7998 END SUBROUTINE salsa_boundary_conditions
     7999
    79568000!------------------------------------------------------------------------------!
    79578001! Description:
Note: See TracChangeset for help on using the changeset viewer.