source: palm/trunk/SOURCE/user_data_output_mask.f90 @ 550

Last change on this file since 550 was 410, checked in by letzel, 14 years ago
  • reintegrate branch letzel/masked_output into trunk; new funtionality: masked data output (not yet documented)
  • Property svn:keywords set to Id
File size: 1.9 KB
Line 
1 SUBROUTINE user_data_output_mask( av, variable, found, local_pf )
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: user_data_output_mask.f90 410 2009-12-04 17:05:40Z maronga $
11! Initial version
12!
13! Description:
14! ------------
15! Resorts the user-defined output quantity with indices (k,j,i) to a
16! temporary array with indices (i,j,k) for masked data output.
17!------------------------------------------------------------------------------!
18
19    USE control_parameters
20    USE indices
21    USE user
22
23    IMPLICIT NONE
24
25    CHARACTER (LEN=*) ::  variable
26
27    INTEGER ::  av, i, j, k
28
29    LOGICAL ::  found
30
31    REAL, DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2), &
32                    mask_size_l(mid,3)) ::  local_pf
33
34
35    found = .TRUE.
36
37    SELECT CASE ( TRIM( variable ) )
38
39!
40!--    Uncomment and extend the following lines, if necessary.
41!--    The arrays for storing the user defined quantities (here u2 and u2_av)
42!--    have to be declared and defined by the user!
43!--    Sample for user-defined output:
44!       CASE ( 'u2' )
45!          IF ( av == 0 )  THEN
46!            DO  i = 1, mask_size_l(mid,1)
47!               DO  j = 1, mask_size_l(mid,2)
48!                  DO  k = 1, mask_size_l(mid,3)
49!                      local_pf(i,j,k) = u2(mask_k(mid,k), &
50!                                           mask_j(mid,j),mask_i(mid,i))
51!                   ENDDO
52!                ENDDO
53!             ENDDO
54!          ELSE
55!            DO  i = 1, mask_size_l(mid,1)
56!               DO  j = 1, mask_size_l(mid,2)
57!                  DO  k = 1, mask_size_l(mid,3)
58!                      local_pf(i,j,k) = u2_av(mask_k(mid,k), &
59!                                              mask_j(mid,j),mask_i(mid,i))
60!                   ENDDO
61!                ENDDO
62!             ENDDO
63!          ENDIF
64!
65
66       CASE DEFAULT
67          found = .FALSE.
68
69    END SELECT
70
71
72 END SUBROUTINE user_data_output_mask
Note: See TracBrowser for help on using the repository browser.