!> @file salsa_util_mod.f90 !--------------------------------------------------------------------------------! ! This file is part of PALM-4U. ! ! PALM-4U is free software: you can redistribute it and/or modify it under the ! terms of the GNU General Public License as published by the Free Software ! Foundation, either version 3 of the License, or (at your option) any later ! version. ! ! PALM-4U is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2018 Leibniz Universitaet Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: salsa_util_mod.f90 3494 2018-11-06 14:51:27Z suehring $ ! Initial revision ! ! ! ! Authors: ! -------- ! @author monakurppa ! ! ! Description: ! ------------ !> Utility functions used in salsa_mod. !------------------------------------------------------------------------------! MODULE salsa_util_mod USE kinds USE pegrid IMPLICIT NONE REAL(wp), DIMENSION(:,:), ALLOCATABLE :: sums_salsa_ws_l !< subdomain sum !< of vertical passive salsa flux w's' !< (5th-order advection scheme only) !-- Component index TYPE component_index INTEGER(iwp) :: ncomp !< Number of components INTEGER(iwp), ALLOCATABLE :: ind(:) !< Component index CHARACTER(len=3), ALLOCATABLE :: comp(:) !< Component name END TYPE component_index SAVE INTERFACE component_index_constructor MODULE PROCEDURE component_index_constructor END INTERFACE component_index_constructor INTERFACE get_index MODULE PROCEDURE get_index END INTERFACE get_index INTERFACE get_n_comp MODULE PROCEDURE get_n_comp END INTERFACE get_n_comp INTERFACE is_used MODULE PROCEDURE is_used END INTERFACE is_used PRIVATE PUBLIC component_index, component_index_constructor, get_index, get_n_comp,& is_used, sums_salsa_ws_l CONTAINS !------------------------------------------------------------------------------! ! Description: ! ------------ !> Creates index tables for different (aerosol) components !------------------------------------------------------------------------------! SUBROUTINE component_index_constructor( SELF, ncomp, nlist, listcomp ) IMPLICIT NONE TYPE(component_index), INTENT(inout) :: SELF !< Object containing the indices !< of different aerosol components INTEGER(iwp), INTENT(inout) :: ncomp !< Number of components INTEGER(iwp), INTENT(in) :: nlist !< Maximum number of components CHARACTER(len=3), INTENT(in) :: listcomp(nlist) !< List cof component !< names INTEGER(iwp) :: i, jj ncomp = 0 DO WHILE ( listcomp(ncomp+1) /= ' ' .AND. ncomp < nlist ) ncomp = ncomp + 1 ENDDO SELF%ncomp = ncomp ALLOCATE( SELF%ind(ncomp), SELF%comp(ncomp) ) DO i = 1, ncomp SELF%ind(i) = i ENDDO jj = 1 DO i = 1, nlist IF ( listcomp(i) == '') CYCLE SELF%comp(jj) = listcomp(i) jj = jj+1 ENDDO END SUBROUTINE component_index_constructor !------------------------------------------------------------------------------! ! Description: ! ------------ !> Gives the index of a component in the component list !------------------------------------------------------------------------------! INTEGER FUNCTION get_index( SELF, incomp ) IMPLICIT NONE TYPE(component_index), INTENT(in) :: SELF !< Object containing the !< indices of different !< aerosol components CHARACTER(len=*), INTENT(in) :: incomp !< Component name INTEGER(iwp) :: i IF ( ANY(SELF%comp == incomp) ) THEN i = 1 DO WHILE ( (SELF%comp(i) /= incomp) ) i = i+1 ENDDO get_index = i ELSEIF ( incomp == 'H2O' ) THEN get_index = SELF%ncomp + 1 ELSE STOP 'get_index: FAILED, no such component -' ENDIF RETURN END FUNCTION get_index !------------------------------------------------------------------------------! ! Description: ! ------------ !> Get the number of (aerosol) components used !------------------------------------------------------------------------------! INTEGER FUNCTION get_n_comp( SELF ) IMPLICIT NONE TYPE(component_index), INTENT(in) :: SELF !< Object containing the !< indices of different !< aerosol components get_n_comp = SELF%ncomp RETURN END FUNCTION !------------------------------------------------------------------------------! ! Description: ! ------------ !> Tells if the (aerosol) component is being used in the simulation !------------------------------------------------------------------------------! LOGICAL FUNCTION is_used( SELF, icomp ) IMPLICIT NONE TYPE(component_index), INTENT(in) :: SELF !< Object containing the !< indices of different !< aerosol components CHARACTER(len=*), INTENT(in) :: icomp !< Component name IF ( ANY(SELF%comp == icomp) ) THEN is_used = .TRUE. ELSE is_used = .FALSE. ENDIF RETURN END FUNCTION END MODULE salsa_util_mod