source: palm/trunk/SOURCE/init_vertical_profiles.f90 @ 4784

Last change on this file since 4784 was 4648, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 5.4 KB
Line 
1!> @file ocean_mod.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 2017-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: init_vertical_profiles.f90 4648 2020-08-25 07:52:08Z suehring $
26! file re-formatted to follow the PALM coding standard
27!
28! 4481 2020-03-31 18:55:54Z maronga
29! split from check_parameters as separate file to avoid circular dependency with ocean_mod
30!
31!
32!
33!
34! Authors:
35! --------
36! @author Siegfried Raasch
37!
38! Description:
39! ------------
40!> Inititalizes the vertical profiles of scalar quantities.
41!--------------------------------------------------------------------------------------------------!
42 SUBROUTINE init_vertical_profiles( vertical_gradient_level_ind,                                   &
43                                    vertical_gradient_level,                                       &
44                                    vertical_gradient, initial_profile,                            &
45                                    surface_value, bc_top_gradient )
46
47    USE arrays_3d,                                                                                 &
48        ONLY:  dzu, zu
49
50    USE control_parameters,                                                                        &
51        ONLY:  ocean_mode
52
53    USE indices,                                                                                   &
54        ONLY:  nz, nzt
55
56    USE kinds
57
58    IMPLICIT NONE
59
60    INTEGER(iwp) ::  i  !< loop counter
61    INTEGER(iwp) ::  k  !< loop counter
62
63    INTEGER(iwp), DIMENSION(1:10) ::  vertical_gradient_level_ind  !< vertical grid indices for gradient levels
64
65    REAL(wp)     ::  bc_top_gradient  !< model top gradient
66    REAL(wp)     ::  gradient         !< vertica gradient of the respective quantity
67    REAL(wp)     ::  surface_value    !< surface value of the respecitve quantity
68
69    REAL(wp), DIMENSION(0:nz+1) ::  initial_profile          !< initialisation profile
70    REAL(wp), DIMENSION(1:10)   ::  vertical_gradient        !< given vertical gradient
71    REAL(wp), DIMENSION(1:10)   ::  vertical_gradient_level  !< given vertical gradient level
72
73    i = 1
74    gradient = 0.0_wp
75
76    IF ( .NOT. ocean_mode )  THEN
77
78       vertical_gradient_level_ind(1) = 0
79       DO  k = 1, nzt+1
80          IF ( i < 11 )  THEN
81             IF ( vertical_gradient_level(i) < zu(k)  .AND.                                        &
82                  vertical_gradient_level(i) >= 0.0_wp )  THEN
83                gradient = vertical_gradient(i) / 100.0_wp
84                vertical_gradient_level_ind(i) = k - 1
85                i = i + 1
86             ENDIF
87          ENDIF
88          IF ( gradient /= 0.0_wp )  THEN
89             IF ( k /= 1 )  THEN
90                initial_profile(k) = initial_profile(k-1) + dzu(k) * gradient
91             ELSE
92                initial_profile(k) = initial_profile(k-1) + dzu(k) * gradient
93             ENDIF
94          ELSE
95             initial_profile(k) = initial_profile(k-1)
96          ENDIF
97!
98!--       Avoid negative values of scalars
99          IF ( initial_profile(k) < 0.0_wp )  THEN
100             initial_profile(k) = 0.0_wp
101          ENDIF
102       ENDDO
103
104    ELSE
105
106!
107!--    In ocean mode, profiles are constructed starting from the ocean surface, which is at the top
108!--    of the model domain
109       vertical_gradient_level_ind(1) = nzt+1
110       DO  k = nzt, 0, -1
111          IF ( i < 11 )  THEN
112             IF ( vertical_gradient_level(i) > zu(k)  .AND.                                        &
113                  vertical_gradient_level(i) <= 0.0_wp )  THEN
114                gradient = vertical_gradient(i) / 100.0_wp
115                vertical_gradient_level_ind(i) = k + 1
116                i = i + 1
117             ENDIF
118          ENDIF
119          IF ( gradient /= 0.0_wp )  THEN
120             IF ( k /= nzt )  THEN
121                initial_profile(k) = initial_profile(k+1) - dzu(k+1) * gradient
122             ELSE
123                initial_profile(k)   = surface_value - 0.5_wp * dzu(k+1) * gradient
124                initial_profile(k+1) = surface_value + 0.5_wp * dzu(k+1) * gradient
125             ENDIF
126          ELSE
127             initial_profile(k) = initial_profile(k+1)
128          ENDIF
129!
130!--       Avoid negative values of scalars
131          IF ( initial_profile(k) < 0.0_wp )  THEN
132             initial_profile(k) = 0.0_wp
133          ENDIF
134       ENDDO
135
136    ENDIF
137
138!
139!-- In case of no given gradients, choose zero gradient conditions
140    IF ( vertical_gradient_level(1) == -999999.9_wp )  THEN
141       vertical_gradient_level(1) = 0.0_wp
142    ENDIF
143!
144!-- Store gradient at the top boundary for possible Neumann boundary condition
145    bc_top_gradient  = ( initial_profile(nzt+1) - initial_profile(nzt) ) / dzu(nzt+1)
146
147 END SUBROUTINE init_vertical_profiles
Note: See TracBrowser for help on using the repository browser.