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

Last change on this file since 3614 was 3494, checked in by suehring, 5 years ago

Surface output revised and some bugs are fixed + new post-processing tool to convert binary surface output to Paraview readable VTK files

  • Property svn:keywords set to Id
File size: 6.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-2018 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: salsa_util_mod.f90 3494 2018-11-06 14:51:27Z raasch $
27! Initial revision
28!
29!
30!
31! Authors:
32! --------
33! @author monakurppa
34!
35!
36! Description:
37! ------------
38!> Utility functions used in salsa_mod.
39!------------------------------------------------------------------------------!
40 MODULE salsa_util_mod
41 
42    USE kinds
43   
44    USE pegrid
45   
46    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)
51
52!-- Component index
53    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   
59    SAVE
60   
61    INTERFACE component_index_constructor
62       MODULE PROCEDURE component_index_constructor
63    END INTERFACE component_index_constructor
64   
65    INTERFACE get_index
66       MODULE PROCEDURE get_index
67    END INTERFACE get_index
68   
69    INTERFACE get_n_comp
70       MODULE PROCEDURE get_n_comp
71    END INTERFACE get_n_comp
72   
73    INTERFACE is_used
74       MODULE PROCEDURE is_used
75    END INTERFACE is_used
76   
77    PRIVATE
78    PUBLIC component_index, component_index_constructor, get_index, get_n_comp,&
79           is_used, sums_salsa_ws_l
80   
81 CONTAINS
82   
83!------------------------------------------------------------------------------!   
84! Description:
85! ------------
86!> Creates index tables for different (aerosol) components
87!------------------------------------------------------------------------------!
88    SUBROUTINE component_index_constructor( SELF, ncomp, nlist, listcomp )
89
90       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       
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       TYPE(component_index), INTENT(in) ::  SELF !< Object containing the
132                                                  !< indices of different
133                                                  !< aerosol components
134       CHARACTER(len=*), INTENT(in) ::  incomp !< Component name
135       INTEGER(iwp) ::  i
136       
137       IF ( ANY(SELF%comp == incomp) ) THEN
138          i = 1
139          DO WHILE ( (SELF%comp(i) /= incomp) )
140             i = i+1
141          ENDDO
142          get_index = i
143       ELSEIF ( incomp == 'H2O' ) THEN
144          get_index = SELF%ncomp + 1
145       ELSE
146          STOP 'get_index: FAILED, no such component -'
147       ENDIF
148       
149       RETURN
150       
151    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
169
170!------------------------------------------------------------------------------!
171! Description:
172! ------------
173!> Tells if the (aerosol) component is being used in the simulation
174!------------------------------------------------------------------------------!
175    LOGICAL FUNCTION is_used( SELF, icomp )
176
177       IMPLICIT NONE
178       
179       TYPE(component_index), INTENT(in) ::  SELF !< Object containing the
180                                                  !< indices of different
181                                                  !< aerosol components
182       CHARACTER(len=*), INTENT(in) ::  icomp !< Component name
183       
184       IF ( ANY(SELF%comp == icomp) ) THEN
185          is_used = .TRUE.
186       ELSE
187          is_used = .FALSE.
188       ENDIF
189       
190       RETURN
191       
192    END FUNCTION
193
194 END MODULE salsa_util_mod
Note: See TracBrowser for help on using the repository browser.