source: palm/trunk/SOURCE/user_flight.f90 @ 3846

Last change on this file since 3846 was 3768, checked in by raasch, 5 years ago

variables commented out + statement added to avoid compiler warnings about unused variables

  • Property svn:keywords set to Id
File size: 3.0 KB
Line 
1!> @file user_flight.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-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: user_flight.f90 3768 2019-02-27 14:35:58Z suehring $
27! unused variables commented out + statement added to avoid compiler warnings
28!
29! 3684 2019-01-20 20:20:58Z knoop
30! Corrected "Former revisions" section
31!
32! 2696 2017-12-14 17:12:51Z kanani
33! Change in file header (GPL part)
34!
35! 2101 2017-01-05 16:42:31Z suehring
36!
37! 2000 2016-08-20 18:09:15Z knoop
38! Forced header and separation lines into 80 columns
39!
40! 1957 2016-07-07 10:43:48Z suehring
41! Initial revision
42!
43! Description:
44! ------------
45!> Calculation of user-defined output quantity for flight measurements after
46!> each timestep.
47!------------------------------------------------------------------------------!
48 SUBROUTINE user_flight( var, id )
49
50    USE control_parameters
51   
52    USE grid_variables
53
54    USE indices
55
56    USE kinds
57
58    USE user
59
60    USE arrays_3d
61
62    IMPLICIT NONE
63
64!    INTEGER(iwp) ::  i  !< index along x
65!    INTEGER(iwp) ::  j  !< index along y
66!    INTEGER(iwp) ::  k  !< index along z
67    INTEGER(iwp) ::  id !< variable identifyer, according to the settings in user_init_flight
68       
69    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !< treated variable
70
71!
72!-- Next line is to avoid compiler warning about unused variables. Please remove.
73    IF ( id == 0  .OR.  var(nzb,nysg,nxlg) == 0.0_wp )  CONTINUE
74
75!
76!-- Here, the respective variable is calculated. There is no call of
77!-- exchange_horiz necessary.
78!-- The variable identifyer (id) must be set according to the settings in
79!-- user_init_flight.
80!-- Please note, so far, variable must be located at the center of a grid box.
81!     var = 0.0_wp
82
83!     SELECT CASE ( id )
84!
85!        CASE ( 1 )
86!           DO i = nxl-1, nxr+1
87!              DO j = nys-1, nyn+1
88!                 DO k = nzb, nzt
89!                    var(k,j,i) = ABS( u(k,j,i )
90!                 ENDDO
91!              ENDDO
92!           ENDDO
93!           
94!        CASE ( 2 )
95!           DO i = nxl-1, nxr+1
96!              DO j = nys-1, nyn+1
97!                 DO k = nzb, nzt
98!                    var(k,j,i) = ABS( v(k,j,i) )
99!                 ENDDO
100!              ENDDO
101!           ENDDO
102!
103!     END SELECT
104
105
106 END SUBROUTINE user_flight
Note: See TracBrowser for help on using the repository browser.