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

Last change on this file since 4186 was 3294, checked in by raasch, 5 years ago

modularization of the ocean code

  • Property svn:keywords set to Id
File size: 5.3 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
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 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 2017-2018 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: init_vertical_profiles.f90 3294 2018-10-01 02:37:10Z suehring $
27! split from check_parameters as separate file to avoid circular dependency
28! with ocean_mod
29!
30!
31!
32!
33! Authors:
34! --------
35! @author Siegfried Raasch
36!
37! Description:
38! ------------
39!> Inititalizes the vertical profiles of scalar quantities.
40!------------------------------------------------------------------------------!
41 SUBROUTINE init_vertical_profiles( vertical_gradient_level_ind,               &
42                                    vertical_gradient_level,                   &
43                                    vertical_gradient, initial_profile,        &
44                                    surface_value, bc_top_gradient )
45
46    USE arrays_3d,                                                             &
47        ONLY:  dzu, zu
48
49    USE control_parameters,                                                    &
50        ONLY:  ocean_mode
51
52    USE indices,                                                               &
53        ONLY:  nz, nzt
54
55    USE kinds
56
57    IMPLICIT NONE
58
59    INTEGER(iwp) ::  i  !< loop counter
60    INTEGER(iwp) ::  k  !< loop counter
61    INTEGER(iwp), DIMENSION(1:10) ::  vertical_gradient_level_ind  !< vertical grid indices for gradient levels
62
63    REAL(wp)     ::  bc_top_gradient  !< model top gradient
64    REAL(wp)     ::  gradient         !< vertica gradient of the respective quantity
65    REAL(wp)     ::  surface_value    !< surface value of the respecitve quantity
66
67    REAL(wp), DIMENSION(0:nz+1) ::  initial_profile          !< initialisation profile
68    REAL(wp), DIMENSION(1:10)   ::  vertical_gradient        !< given vertical gradient
69    REAL(wp), DIMENSION(1:10)   ::  vertical_gradient_level  !< given vertical gradient level
70
71    i = 1
72    gradient = 0.0_wp
73
74    IF ( .NOT. ocean_mode )  THEN
75
76       vertical_gradient_level_ind(1) = 0
77       DO  k = 1, nzt+1
78          IF ( i < 11 )  THEN
79             IF ( vertical_gradient_level(i) < zu(k)  .AND.            &
80                  vertical_gradient_level(i) >= 0.0_wp )  THEN
81                gradient = vertical_gradient(i) / 100.0_wp
82                vertical_gradient_level_ind(i) = k - 1
83                i = i + 1
84             ENDIF
85          ENDIF
86          IF ( gradient /= 0.0_wp )  THEN
87             IF ( k /= 1 )  THEN
88                initial_profile(k) = initial_profile(k-1) + dzu(k) * gradient
89             ELSE
90                initial_profile(k) = initial_profile(k-1) + dzu(k) * gradient
91             ENDIF
92          ELSE
93             initial_profile(k) = initial_profile(k-1)
94          ENDIF
95!
96!--       Avoid negative values of scalars
97          IF ( initial_profile(k) < 0.0_wp )  THEN
98             initial_profile(k) = 0.0_wp
99          ENDIF
100       ENDDO
101
102    ELSE
103
104!
105!--    In ocean mode, profiles are constructed starting from the ocean surface,
106!--    which is at the top of the model domain
107       vertical_gradient_level_ind(1) = nzt+1
108       DO  k = nzt, 0, -1
109          IF ( i < 11 )  THEN
110             IF ( vertical_gradient_level(i) > zu(k)  .AND.            &
111                  vertical_gradient_level(i) <= 0.0_wp )  THEN
112                gradient = vertical_gradient(i) / 100.0_wp
113                vertical_gradient_level_ind(i) = k + 1
114                i = i + 1
115             ENDIF
116          ENDIF
117          IF ( gradient /= 0.0_wp )  THEN
118             IF ( k /= nzt )  THEN
119                initial_profile(k) = initial_profile(k+1) - dzu(k+1) * gradient
120             ELSE
121                initial_profile(k)   = surface_value - 0.5_wp * dzu(k+1) *     &
122                                                       gradient
123                initial_profile(k+1) = surface_value + 0.5_wp * dzu(k+1) *     &
124                                                       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) ) /     &
146                       dzu(nzt+1)
147
148 END SUBROUTINE init_vertical_profiles
Note: See TracBrowser for help on using the repository browser.