source: palm/trunk/SOURCE/advec_s_pw.f90 @ 1320

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 5.9 KB
Line 
1 MODULE advec_s_pw_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! revision history before 2012 removed,
26! comment fields (!:) to be used for variable explanations added to
27! all variable declaration statements
28!
29! Former revisions:
30! -----------------
31! $Id: advec_s_pw.f90 1320 2014-03-20 08:40:49Z raasch $
32!
33! 1036 2012-10-22 13:43:42Z raasch
34! code put under GPL (PALM 3.9)
35!
36! 1010 2012-09-20 07:59:54Z raasch
37! cpp switch __nopointer added for pointer free version
38!
39! Revision 1.1  1997/08/29 08:54:20  raasch
40! Initial revision
41!
42!
43! Description:
44! ------------
45! Advection term for scalar variables using the Piacsek and Williams scheme
46! (form C3). Contrary to PW itself, for reasons of accuracy their scheme is
47! slightly modified as follows: the values of those scalars that are used for
48! the computation of the flux divergence are reduced by the value of the
49! relevant scalar at the location where the difference is computed (sk(k,j,i)).
50! NOTE: at the first grid point above the surface computation still takes place!
51!------------------------------------------------------------------------------!
52
53    PRIVATE
54    PUBLIC advec_s_pw
55
56    INTERFACE advec_s_pw
57       MODULE PROCEDURE advec_s_pw
58       MODULE PROCEDURE advec_s_pw_ij
59    END INTERFACE
60 
61 CONTAINS
62
63
64!------------------------------------------------------------------------------!
65! Call for all grid points
66!------------------------------------------------------------------------------!
67    SUBROUTINE advec_s_pw( sk )
68
69       USE arrays_3d,                                                          &
70           ONLY:  dd2zu, tend, u, v, w
71
72       USE control_parameters,                                                 &
73           ONLY:  u_gtrans, v_gtrans
74
75       USE grid_variables,                                                     &
76           ONLY:  ddx, ddy
77
78       USE indices,                                                            &
79           ONLY:  nxl, nxr, nyn, nys, nzb_s_inner, nzt
80
81       USE kinds
82
83
84       IMPLICIT NONE
85
86       INTEGER(iwp) ::  i !:
87       INTEGER(iwp) ::  j !:
88       INTEGER(iwp) ::  k !:
89
90#if defined( __nopointer )
91       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
92#else
93       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
94#endif
95 
96
97       DO  i = nxl, nxr
98          DO  j = nys, nyn
99             DO  k = nzb_s_inner(j,i)+1, nzt
100                tend(k,j,i) = tend(k,j,i)                                      &
101              -0.5 * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
102                     - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
103                     ) * ddx                                                   &
104              -0.5 * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
105                     - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
106                     ) * ddy                                                   &
107              -      (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
108                     -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
109                     ) * dd2zu(k)
110             ENDDO
111          ENDDO
112       ENDDO
113
114    END SUBROUTINE advec_s_pw
115
116
117!------------------------------------------------------------------------------!
118! Call for grid point i,j
119!------------------------------------------------------------------------------!
120    SUBROUTINE advec_s_pw_ij( i, j, sk )
121
122       USE arrays_3d,                                                          &
123           ONLY:  dd2zu, tend, u, v, w
124
125       USE control_parameters,                                                 &
126           ONLY:  u_gtrans, v_gtrans
127
128       USE grid_variables,                                                     &
129           ONLY:  ddx, ddy
130
131       USE indices,                                                            &
132           ONLY:  nzb_s_inner, nzt
133
134       USE kinds
135
136
137       IMPLICIT NONE
138
139       INTEGER(iwp) ::  i !:
140       INTEGER(iwp) ::  j !:
141       INTEGER(iwp) ::  k !:
142
143#if defined( __nopointer )
144       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
145#else
146       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
147#endif
148
149
150       DO  k = nzb_s_inner(j,i)+1, nzt
151          tend(k,j,i) = tend(k,j,i)                                            &
152              -0.5 * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
153                     - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
154                     ) * ddx                                                   &
155              -0.5 * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
156                     - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
157                     ) * ddy                                                   &
158              -      (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
159                     -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
160                     ) * dd2zu(k)
161       ENDDO
162
163    END SUBROUTINE advec_s_pw_ij
164
165 END MODULE advec_s_pw_mod
Note: See TracBrowser for help on using the repository browser.