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

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

last commit documented

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