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

Last change on this file since 915 was 668, checked in by suehring, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 2.0 KB
Line 
1 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7! Former revisions:
8! -----------------
9! $Id: user_data_output_2d.f90 668 2010-12-23 13:22:58Z maronga $
10!
11! 667 2010-12-23 12:06:00Z suehring/gryschka
12! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
13!
14! 343 2009-06-24 12:59:09Z maronga
15! +dummy argument two_d
16!
17! 211 2008-11-11 04:46:24Z raasch
18! Former file user_interface.f90 split into one file per subroutine
19!
20! Description:
21! ------------
22! Resorts the user-defined output quantity with indices (k,j,i) to a
23! temporary array with indices (i,j,k) and sets the grid on which it is defined.
24! Allowed values for grid are "zu" and "zw".
25!------------------------------------------------------------------------------!
26
27    USE indices
28    USE user
29
30    IMPLICIT NONE
31
32    CHARACTER (LEN=*) ::  grid, variable
33
34    INTEGER ::  av, i, j, k
35
36    LOGICAL ::  found, two_d
37
38    REAL, DIMENSION(nxlg:nxrg,nysg:nyng,nzb:nzt+1) ::  local_pf
39
40
41    found = .TRUE.
42
43    SELECT CASE ( TRIM( variable ) )
44
45!
46!--    Uncomment and extend the following lines, if necessary.
47!--    The arrays for storing the user defined quantities (here u2 and u2_av)
48!--    have to be declared and defined by the user!
49!--    Sample for user-defined output:
50!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
51!          IF ( av == 0 )  THEN
52!             DO  i = nxlg, nxrg
53!                DO  j = nysg, nyng
54!                   DO  k = nzb, nzt+1
55!                      local_pf(i,j,k) = u2(k,j,i)
56!                   ENDDO
57!                ENDDO
58!             ENDDO
59!          ELSE
60!             DO  i = nxlg, nxrg
61!                DO  j = nysg, nyng
62!                   DO  k = nzb, nzt+1
63!                      local_pf(i,j,k) = u2_av(k,j,i)
64!                   ENDDO
65!                ENDDO
66!             ENDDO
67!          ENDIF
68!
69!          grid = 'zu'
70
71
72       CASE DEFAULT
73          found = .FALSE.
74          grid  = 'none'
75
76    END SELECT
77
78
79 END SUBROUTINE user_data_output_2d
80
Note: See TracBrowser for help on using the repository browser.