source: palm/trunk/SOURCE/advec_u_pw.f90 @ 3385

Last change on this file since 3385 was 2718, checked in by maronga, 6 years ago

deleting of deprecated files; headers updated where needed

  • Property svn:keywords set to Id
File size: 6.5 KB
Line 
1!> @file advec_u_pw.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 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: advec_u_pw.f90 2718 2018-01-02 08:49:38Z knoop $
27! Corrected "Former revisions" section
28!
29! 2696 2017-12-14 17:12:51Z kanani
30! Change in file header (GPL part)
31!
32! 2233 2017-05-30 18:08:54Z suehring
33!
34! 2232 2017-05-30 17:47:52Z suehring
35! topography representation via flags
36!
37! 2000 2016-08-20 18:09:15Z knoop
38! Forced header and separation lines into 80 columns
39!
40! 1873 2016-04-18 14:50:06Z maronga
41! Module renamed (removed _mod)
42!
43!
44! 1850 2016-04-08 13:29:27Z maronga
45! Module renamed
46!
47!
48! 1682 2015-10-07 23:56:08Z knoop
49! Code annotations made doxygen readable
50!
51! 1353 2014-04-08 15:21:23Z heinze
52! REAL constants provided with KIND-attribute
53!
54! 1320 2014-03-20 08:40:49Z raasch
55! ONLY-attribute added to USE-statements,
56! kind-parameters added to all INTEGER and REAL declaration statements,
57! kinds are defined in new module kinds,
58! revision history before 2012 removed,
59! comment fields (!:) to be used for variable explanations added to
60! all variable declaration statements
61!
62! 1036 2012-10-22 13:43:42Z raasch
63! code put under GPL (PALM 3.9)
64!
65! Revision 1.1  1997/08/11 06:09:21  raasch
66! Initial revision
67!
68!
69! Description:
70! ------------
71!> Advection term for u velocity-component using Piacsek and Williams.
72!> Vertical advection at the first grid point above the surface is done with
73!> normal centred differences, because otherwise no information from the surface
74!> would be communicated upwards due to w=0 at K=nzb.
75!------------------------------------------------------------------------------!
76 MODULE advec_u_pw_mod
77 
78
79    PRIVATE
80    PUBLIC advec_u_pw
81
82    INTERFACE advec_u_pw
83       MODULE PROCEDURE advec_u_pw
84       MODULE PROCEDURE advec_u_pw_ij
85    END INTERFACE advec_u_pw
86 
87 CONTAINS
88
89
90!------------------------------------------------------------------------------!
91! Description:
92! ------------
93!> Call for all grid points
94!------------------------------------------------------------------------------!
95    SUBROUTINE advec_u_pw
96
97       USE arrays_3d,                                                          &
98           ONLY:  ddzw, tend, u, v, w
99
100       USE control_parameters,                                                 &
101           ONLY:  u_gtrans, v_gtrans
102
103       USE grid_variables,                                                     &
104           ONLY:  ddx, ddy
105
106       USE indices,                                                            &
107           ONLY:  nxlu, nxr, nyn, nys, nzb, nzt, wall_flags_0
108
109       USE kinds
110
111
112       IMPLICIT NONE
113
114       INTEGER(iwp) ::  i !<
115       INTEGER(iwp) ::  j !<
116       INTEGER(iwp) ::  k !<
117       
118       REAL(wp)    ::  gu !<
119       REAL(wp)    ::  gv !<
120 
121       gu = 2.0_wp * u_gtrans
122       gv = 2.0_wp * v_gtrans
123       DO  i = nxlu, nxr
124          DO  j = nys, nyn
125             DO  k = nzb+1, nzt
126                tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                        &
127                         ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
128                         - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
129                       + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
130                         - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
131                       + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
132                         - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
133                                                                  * ddzw(k)    &
134                                                      )                        &
135                                      * MERGE( 1.0_wp, 0.0_wp,                 &
136                                               BTEST( wall_flags_0(k,j,i), 1 ) )
137             ENDDO
138          ENDDO
139       ENDDO
140
141    END SUBROUTINE advec_u_pw
142
143
144!------------------------------------------------------------------------------!
145! Description:
146! ------------
147!> Call for grid point i,j
148!------------------------------------------------------------------------------!
149    SUBROUTINE advec_u_pw_ij( i, j )
150
151       USE arrays_3d,                                                          &
152           ONLY:  ddzw, tend, u, v, w
153
154       USE control_parameters,                                                 &
155           ONLY:  u_gtrans, v_gtrans
156
157       USE grid_variables,                                                     &
158           ONLY:  ddx, ddy
159
160       USE indices,                                                            &
161           ONLY:  nzb, nzt, wall_flags_0
162
163       USE kinds
164
165
166       IMPLICIT NONE
167
168       INTEGER(iwp) ::  i !<
169       INTEGER(iwp) ::  j !<
170       INTEGER(iwp) ::  k !<
171       
172       REAL(wp)    ::  gu !<
173       REAL(wp)    ::  gv !<
174
175       gu = 2.0_wp * u_gtrans
176       gv = 2.0_wp * v_gtrans
177       DO  k = nzb+1, nzt
178          tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                              &
179                         ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
180                         - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
181                       + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
182                         - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
183                       + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
184                         - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
185                                                                  * ddzw(k)    &
186                                                )                              &
187                                      * MERGE( 1.0_wp, 0.0_wp,                 &
188                                               BTEST( wall_flags_0(k,j,i), 1 ) )
189       ENDDO
190
191    END SUBROUTINE advec_u_pw_ij
192
193 END MODULE advec_u_pw_mod
Note: See TracBrowser for help on using the repository browser.