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

Last change on this file since 1354 was 1354, checked in by heinze, 10 years ago

last commit documented

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