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

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

Moving prognostic equations of bcm into bulk_cloud_model_mod

  • Property svn:keywords set to Id
File size: 5.1 KB
Line 
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!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: salsa_util_mod.f90 3871 2019-04-08 14:38:39Z knoop $
27! Formatting changes
28!
29! 3845 2019-04-01 13:41:55Z monakurppa
30! Initial revision
31!
32!
33!
34! Authors:
35! --------
36! @author monakurppa
37!
38!
39! Description:
40! ------------
41!> Utility functions used in salsa_mod.
42!------------------------------------------------------------------------------!
43 MODULE salsa_util_mod
44
45    USE control_parameters,                                                                        &
46        ONLY:  message_string
47
48    USE kinds
49
50    USE pegrid
51
52    IMPLICIT NONE
53!
54!-- Component index
55    TYPE component_index
56       INTEGER(iwp) ::  ncomp  !< Number of components
57       INTEGER(iwp), ALLOCATABLE ::  ind(:)  !< Component index
58       CHARACTER(len=3), ALLOCATABLE ::  comp(:)  !< Component name
59    END TYPE component_index
60
61    SAVE
62
63    INTERFACE component_index_constructor
64       MODULE PROCEDURE component_index_constructor
65    END INTERFACE component_index_constructor
66
67    INTERFACE get_index
68       MODULE PROCEDURE get_index
69    END INTERFACE get_index
70
71    INTERFACE is_used
72       MODULE PROCEDURE is_used
73    END INTERFACE is_used
74
75    PRIVATE
76    PUBLIC component_index, component_index_constructor, get_index, is_used
77
78 CONTAINS
79
80!------------------------------------------------------------------------------!
81! Description:
82! ------------
83!> Creates index tables for different (aerosol) components
84!------------------------------------------------------------------------------!
85    SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
86
87       IMPLICIT NONE
88
89       INTEGER(iwp) ::  i   !<
90       INTEGER(iwp) ::  jj  !<
91
92       INTEGER(iwp), INTENT(in) ::  nlist ! < Maximum number of components
93
94       INTEGER(iwp), INTENT(inout) ::  ncomp  !< Number of components
95
96       TYPE(component_index), INTENT(inout) ::  self  !< Object containing the indices of different
97                                                      !< aerosol components
98       CHARACTER(len=3), INTENT(in) ::  listcomp(nlist)  !< List cof component names
99
100       ncomp = 0
101
102       DO WHILE ( listcomp(ncomp+1) /= '  ' .AND. ncomp < nlist )
103          ncomp = ncomp + 1
104       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
111       ENDDO
112
113       jj = 1
114       DO  i = 1, nlist
115          IF ( listcomp(i) == '') CYCLE
116          self%comp(jj) = listcomp(i)
117          jj = jj + 1
118       ENDDO
119
120    END SUBROUTINE component_index_constructor
121
122!------------------------------------------------------------------------------!
123! Description:
124! ------------
125!> Gives the index of a component in the component list
126!------------------------------------------------------------------------------!
127    INTEGER FUNCTION get_index( self, incomp )
128
129       IMPLICIT NONE
130
131       CHARACTER(len=*), INTENT(in) ::  incomp !< Component name
132       INTEGER(iwp) ::  i
133
134       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
135                                                   !< aerosol components
136       IF ( ANY( self%comp == incomp ) ) THEN
137          i = 1
138          DO WHILE ( (self%comp(i) /= incomp) )
139             i = i + 1
140          ENDDO
141          get_index = i
142       ELSEIF ( incomp == 'H2O' ) THEN
143          get_index = self%ncomp + 1
144       ELSE
145          WRITE( message_string, * ) 'Incorrect component name given!'
146          CALL message( 'get_index', 'PA0591', 1, 2, 0, 6, 0 )
147       ENDIF
148
149       RETURN
150
151    END FUNCTION get_index
152
153!------------------------------------------------------------------------------!
154! Description:
155! ------------
156!> Tells if the (aerosol) component is being used in the simulation
157!------------------------------------------------------------------------------!
158    LOGICAL FUNCTION is_used( self, icomp )
159
160       IMPLICIT NONE
161
162       CHARACTER(len=*), INTENT(in) ::  icomp !< Component name
163
164       TYPE(component_index), INTENT(in) ::  self  !< Object containing the indices of different
165                                                   !< aerosol components
166
167       IF ( ANY(self%comp == icomp) ) THEN
168          is_used = .TRUE.
169       ELSE
170          is_used = .FALSE.
171       ENDIF
172
173    END FUNCTION
174
175 END MODULE salsa_util_mod
Note: See TracBrowser for help on using the repository browser.