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

Last change on this file since 1036 was 1036, checked in by raasch, 11 years ago

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 4.8 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: advec_s_pw.f90 1036 2012-10-22 13:43:42Z raasch $
27!
28! 1010 2012-09-20 07:59:54Z raasch
29! cpp switch __nopointer added for pointer free version
30!
31! 19 2007-02-23 04:53:48Z raasch
32! Calculation extended for gridpoint nzt
33!
34! RCS Log replace by Id keyword, revision history cleaned up
35!
36! Revision 1.12  2006/02/23 09:42:55  raasch
37! nzb_2d replaced by nzb_s_inner
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       USE control_parameters
71       USE grid_variables
72       USE indices
73
74       IMPLICIT NONE
75
76       INTEGER ::  i, j, k
77
78#if defined( __nopointer )
79       REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
80#else
81       REAL, DIMENSION(:,:,:), POINTER ::  sk
82#endif
83 
84
85       DO  i = nxl, nxr
86          DO  j = nys, nyn
87             DO  k = nzb_s_inner(j,i)+1, nzt
88                tend(k,j,i) = tend(k,j,i)                                      &
89              -0.5 * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
90                     - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
91                     ) * ddx                                                   &
92              -0.5 * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
93                     - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
94                     ) * ddy                                                   &
95              -      (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
96                     -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
97                     ) * dd2zu(k)
98             ENDDO
99          ENDDO
100       ENDDO
101
102    END SUBROUTINE advec_s_pw
103
104
105!------------------------------------------------------------------------------!
106! Call for grid point i,j
107!------------------------------------------------------------------------------!
108    SUBROUTINE advec_s_pw_ij( i, j, sk )
109
110       USE arrays_3d
111       USE control_parameters
112       USE grid_variables
113       USE indices
114
115       IMPLICIT NONE
116
117       INTEGER ::  i, j, k
118
119#if defined( __nopointer )
120       REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
121#else
122       REAL, DIMENSION(:,:,:), POINTER ::  sk
123#endif
124
125
126       DO  k = nzb_s_inner(j,i)+1, nzt
127          tend(k,j,i) = tend(k,j,i)                                            &
128              -0.5 * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
129                     - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
130                     ) * ddx                                                   &
131              -0.5 * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
132                     - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
133                     ) * ddy                                                   &
134              -      (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
135                     -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
136                     ) * dd2zu(k)
137       ENDDO
138
139    END SUBROUTINE advec_s_pw_ij
140
141 END MODULE advec_s_pw_mod
Note: See TracBrowser for help on using the repository browser.