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

Last change on this file since 3385 was 3014, checked in by maronga, 6 years ago

series of bugfixes

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