source: palm/trunk/SOURCE/user_data_output_2d.f90 @ 2716

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

  • Property svn:keywords set to Id
File size: 5.5 KB
Line 
1!> @file user_data_output_2d.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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: user_data_output_2d.f90 2716 2017-12-29 16:35:59Z kanani $
27! Corrected "Former revisions" section
28!
29! 2696 2017-12-14 17:12:51Z kanani
30! Change in file header (GPL part)
31!
32! 2512 2017-10-04 08:26:59Z raasch
33! ghost layer points removed from output array local_pf
34!
35! 2233 2017-05-30 18:08:54Z suehring
36!
37! 2232 2017-05-30 17:47:52Z suehring
38! Example code added for accessing output quantities stored on surface-data
39! types
40!
41! 2000 2016-08-20 18:09:15Z knoop
42! Forced header and separation lines into 80 columns
43!
44! 1682 2015-10-07 23:56:08Z knoop
45! Code annotations made doxygen readable
46!
47! 1551 2015-03-03 14:18:16Z maronga
48! Replaced nzb and nzt+1 with the new array bounds nzb_do and nzt_do.
49!
50! 1320 2014-03-20 08:40:49Z raasch
51! kind-parameters added to all INTEGER and REAL declaration statements,
52! kinds are defined in new module kinds,
53! revision history before 2012 removed,
54! comment fields (!:) to be used for variable explanations added to
55! all variable declaration statements
56!
57! 1036 2012-10-22 13:43:42Z raasch
58! code put under GPL (PALM 3.9)
59!
60! 211 2008-11-11 04:46:24Z raasch
61! Former file user_interface.f90 split into one file per subroutine
62!
63! Description:
64! ------------
65!> Resorts the user-defined output quantity with indices (k,j,i) to a
66!> temporary array with indices (i,j,k) and sets the grid on which it is defined.
67!> Allowed values for grid are "zu" and "zw".
68!------------------------------------------------------------------------------!
69 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do )
70 
71
72    USE indices
73
74    USE kinds
75
76    USE surface_mod
77
78    USE user
79
80    IMPLICIT NONE
81
82    CHARACTER (LEN=*) ::  grid     !<
83    CHARACTER (LEN=*) ::  variable !<
84
85    INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
86    INTEGER(iwp) ::  i      !< grid index along x-direction
87    INTEGER(iwp) ::  j      !< grid index along y-direction
88    INTEGER(iwp) ::  k      !< grid index along z-direction
89    INTEGER(iwp) ::  m      !< running index surface elements
90    INTEGER(iwp) ::  nzb_do !< lower limit of the domain (usually nzb)
91    INTEGER(iwp) ::  nzt_do !< upper limit of the domain (usually nzt+1)
92
93    LOGICAL      ::  found !<
94    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
95
96    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
97
98
99    found = .TRUE.
100
101    SELECT CASE ( TRIM( variable ) )
102
103!
104!--    Uncomment and extend the following lines, if necessary.
105!--    The arrays for storing the user defined quantities (here u2 and u2_av)
106!--    have to be declared and defined by the user!
107!--    Sample for user-defined output:
108!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
109!          IF ( av == 0 )  THEN
110!             DO  i = nxl, nxr
111!                DO  j = nys, nyn
112!                   DO  k = nzb_do, nzt_do
113!                      local_pf(i,j,k) = u2(k,j,i)
114!                   ENDDO
115!                ENDDO
116!             ENDDO
117!          ELSE
118!             DO  i = nxl, nxr
119!                DO  j = nys, nyn
120!                   DO  k = nzb_do, nzt_do
121!                      local_pf(i,j,k) = u2_av(k,j,i)
122!                   ENDDO
123!                ENDDO
124!             ENDDO
125!          ENDIF
126!
127!          grid = 'zu'
128!
129!--    In case two-dimensional surface variables are output, the user
130!--    has to access related surface-type. Uncomment and extend following lines
131!--    appropriately (example output of vertical surface momentum flux of u-
132!--    component). Please note, surface elements can be distributed over
133!--    several data type, depending on their respective surface properties.
134!       CASE ( 'usws_xy' )
135!          IF ( av == 0 )  THEN
136!
137!--           Horizontal default-type surfaces
138!             DO  m = 1, surf_def_h(0)%ns
139!                i = surf_def_h(0)%i(m)
140!                j = surf_def_h(0)%j(m)
141!                local_pf(i,j,1) = surf_def_h(0)%usws(m)
142!             ENDDO
143!
144!--           Horizontal natural-type surfaces
145!             DO  m = 1, surf_lsm_h%ns
146!                i = surf_lsm_h%i(m)
147!                j = surf_lsm_h%j(m)
148!                local_pf(i,j,1) = surf_lsm_h%usws(m)
149!             ENDDO
150!
151!--           Horizontal urban-type surfaces
152!             DO  m = 1, surf_usm_h%ns
153!                i = surf_usm_h%i(m)
154!                j = surf_usm_h%j(m)
155!                local_pf(i,j,1) = surf_usm_h%usws(m)
156!             ENDDO
157!          ENDIF
158!
159!          grid = 'zu'
160!--       
161
162
163       CASE DEFAULT
164          found = .FALSE.
165          grid  = 'none'
166
167    END SELECT
168
169
170 END SUBROUTINE user_data_output_2d
Note: See TracBrowser for help on using the repository browser.