source: palm/trunk/SOURCE/salsa_util_mod.f90 @ 3872

Last change on this file since 3872 was 3872, checked in by knoop, 5 years ago

Including last commit, salsa dependency for advec_ws removed

  • Property svn:keywords set to Id
File size: 5.2 KB
RevLine 
[2505]1!> @file salsa_util_mod.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM-4U.
4!
5! PALM-4U is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM-4U is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[3655]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[2505]18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
[2525]23!
[2505]24! Former revisions:
25! -----------------
26! $Id: salsa_util_mod.f90 3872 2019-04-08 15:03:06Z knoop $
[3872]27! moved decrlaration of sums_salsa_ws_l to statistics module
28!
29! 3871 2019-04-08 14:38:39Z knoop
[3864]30! Formatting changes
31!
32! 3845 2019-04-01 13:41:55Z monakurppa
[2525]33! Initial revision
[2505]34!
[3864]35!
36!
[2505]37! Authors:
38! --------
39! @author monakurppa
40!
41!
42! Description:
43! ------------
44!> Utility functions used in salsa_mod.
45!------------------------------------------------------------------------------!
46 MODULE salsa_util_mod
[3864]47
48    USE control_parameters,                                                                        &
49        ONLY:  message_string
50
[2505]51    USE kinds
[3864]52
[2754]53    USE pegrid
[3864]54
[2505]55    IMPLICIT NONE
[3864]56!
[2505]57!-- Component index
58    TYPE component_index
[3864]59       INTEGER(iwp) ::  ncomp  !< Number of components
60       INTEGER(iwp), ALLOCATABLE ::  ind(:)  !< Component index
61       CHARACTER(len=3), ALLOCATABLE ::  comp(:)  !< Component name
62    END TYPE component_index
63
[2505]64    SAVE
[3864]65
[2505]66    INTERFACE component_index_constructor
67       MODULE PROCEDURE component_index_constructor
68    END INTERFACE component_index_constructor
[3864]69
[2505]70    INTERFACE get_index
71       MODULE PROCEDURE get_index
72    END INTERFACE get_index
[3864]73
[2505]74    INTERFACE is_used
75       MODULE PROCEDURE is_used
76    END INTERFACE is_used
[3864]77
[2505]78    PRIVATE
[3871]79    PUBLIC component_index, component_index_constructor, get_index, is_used
[3864]80
[2505]81 CONTAINS
[3864]82
83!------------------------------------------------------------------------------!
[2505]84! Description:
85! ------------
86!> Creates index tables for different (aerosol) components
87!------------------------------------------------------------------------------!
[3864]88    SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
[2505]89
90       IMPLICIT NONE
[3864]91
92       INTEGER(iwp) ::  i   !<
93       INTEGER(iwp) ::  jj  !<
94
95       INTEGER(iwp), INTENT(in) ::  nlist ! < Maximum number of components
96
97       INTEGER(iwp), INTENT(inout) ::  ncomp  !< Number of components
98
99       TYPE(component_index), INTENT(inout) ::  self  !< Object containing the indices of different
100                                                      !< aerosol components
101       CHARACTER(len=3), INTENT(in) ::  listcomp(nlist)  !< List cof component names
102
[2754]103       ncomp = 0
[3864]104
105       DO WHILE ( listcomp(ncomp+1) /= '  ' .AND. ncomp < nlist )
[2754]106          ncomp = ncomp + 1
107       ENDDO
[3864]108
109       self%ncomp = ncomp
110       ALLOCATE( self%ind(ncomp), self%comp(ncomp) )
111
112       DO  i = 1, ncomp
113          self%ind(i) = i
[2505]114       ENDDO
[3864]115
[2505]116       jj = 1
[3864]117       DO  i = 1, nlist
[2505]118          IF ( listcomp(i) == '') CYCLE
[3864]119          self%comp(jj) = listcomp(i)
120          jj = jj + 1
[2505]121       ENDDO
[3864]122
[2505]123    END SUBROUTINE component_index_constructor
124
125!------------------------------------------------------------------------------!
126! Description:
127! ------------
128!> Gives the index of a component in the component list
129!------------------------------------------------------------------------------!
[3864]130    INTEGER FUNCTION get_index( self, incomp )
[2505]131
132       IMPLICIT NONE
[3864]133
[2505]134       CHARACTER(len=*), INTENT(in) ::  incomp !< Component name
135       INTEGER(iwp) ::  i
[3864]136
137       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
138                                                   !< aerosol components
139       IF ( ANY( self%comp == incomp ) ) THEN
[2505]140          i = 1
[3864]141          DO WHILE ( (self%comp(i) /= incomp) )
142             i = i + 1
[2505]143          ENDDO
144          get_index = i
145       ELSEIF ( incomp == 'H2O' ) THEN
[3864]146          get_index = self%ncomp + 1
[2505]147       ELSE
[3864]148          WRITE( message_string, * ) 'Incorrect component name given!'
149          CALL message( 'get_index', 'PA0591', 1, 2, 0, 6, 0 )
[2505]150       ENDIF
[3864]151
[2505]152       RETURN
[3864]153
[2505]154    END FUNCTION get_index
155
156!------------------------------------------------------------------------------!
157! Description:
158! ------------
[3864]159!> Tells if the (aerosol) component is being used in the simulation
[2505]160!------------------------------------------------------------------------------!
[3864]161    LOGICAL FUNCTION is_used( self, icomp )
[2505]162
163       IMPLICIT NONE
164
[3864]165       CHARACTER(len=*), INTENT(in) ::  icomp !< Component name
[2505]166
[3864]167       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
168                                                   !< aerosol components
[2505]169
[3864]170       IF ( ANY(self%comp == icomp) ) THEN
[2505]171          is_used = .TRUE.
172       ELSE
173          is_used = .FALSE.
174       ENDIF
[3864]175
[2505]176    END FUNCTION
[3467]177
[2505]178 END MODULE salsa_util_mod
Note: See TracBrowser for help on using the repository browser.