source: palm/trunk/SOURCE/user_actions.f90 @ 258

Last change on this file since 258 was 258, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

  • Property svn:keywords set to Id
File size: 4.3 KB
Line 
1 MODULE user_actions_mod
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Output of messages replaced by message handling routine.
7!
8!
9! Former revisions:
10! -----------------
11! $Id: user_actions.f90 258 2009-03-13 12:36:03Z heinze $
12!
13! 211 2008-11-11 04:46:24Z raasch
14! Former file user_interface.f90 split into one file per subroutine
15!
16! Description:
17! ------------
18! Execution of user-defined actions before or after single timesteps
19!------------------------------------------------------------------------------!
20
21    PRIVATE
22    PUBLIC user_actions
23
24    INTERFACE user_actions
25       MODULE PROCEDURE user_actions
26       MODULE PROCEDURE user_actions_ij
27    END INTERFACE user_actions
28
29 CONTAINS
30
31
32!------------------------------------------------------------------------------!
33! Call for all grid points
34!------------------------------------------------------------------------------!
35    SUBROUTINE user_actions( location )
36
37       USE control_parameters
38       USE cpulog
39       USE indices
40       USE interfaces
41       USE pegrid
42       USE user
43       USE arrays_3d
44
45       IMPLICIT NONE
46
47       CHARACTER (LEN=*) ::  location
48
49       INTEGER ::  i, j, k
50
51       CALL cpu_log( log_point(24), 'user_actions', 'start' )
52
53!
54!--    Here the user-defined actions follow
55!--    No calls for single grid points are allowed at locations before and
56!--    after the timestep, since these calls are not within an i,j-loop
57       SELECT CASE ( location )
58
59          CASE ( 'before_timestep' )
60!
61!--          Enter actions to be done before every timestep here
62
63
64          CASE ( 'after_integration' )
65!
66!--          Enter actions to be done after every time integration (before
67!--          data output)
68!--          Sample for user-defined output:
69!             DO  i = nxl-1, nxr+1
70!                DO  j = nys-1, nyn+1
71!                   DO  k = nzb, nzt+1
72!                      u2(k,j,i) = u(k,j,i)**2
73!                   ENDDO
74!                ENDDO
75!             ENDDO
76!             DO  i = nxl-1, nxr
77!                DO  j = nys-1, nyn
78!                   DO  k = nzb, nzt+1
79!                      ustvst(k,j,i) =  &
80!                         ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
81!                         ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
82!                   ENDDO
83!                ENDDO
84!             ENDDO
85
86
87          CASE ( 'after_timestep' )
88!
89!--          Enter actions to be done after every timestep here
90
91
92          CASE ( 'u-tendency' )
93!
94!--          Enter actions to be done in the u-tendency term here
95
96
97          CASE ( 'v-tendency' )
98
99
100          CASE ( 'w-tendency' )
101
102
103          CASE ( 'pt-tendency' )
104
105
106          CASE ( 'sa-tendency' )
107
108
109          CASE ( 'e-tendency' )
110
111
112          CASE ( 'q-tendency' )
113
114
115          CASE DEFAULT
116             message_string = 'unknown location "' // location // '"'
117             CALL message( 'user_actions', 'UI0001', 1, 2, 0, 6, 0 )
118
119       END SELECT
120
121       CALL cpu_log( log_point(24), 'user_actions', 'stop' )
122
123    END SUBROUTINE user_actions
124
125
126!------------------------------------------------------------------------------!
127! Call for grid point i,j
128!------------------------------------------------------------------------------!
129    SUBROUTINE user_actions_ij( i, j, location )
130
131       USE control_parameters
132       USE pegrid
133       USE user
134
135       IMPLICIT NONE
136
137       CHARACTER (LEN=*) ::  location
138
139       INTEGER ::  i, idum, j
140
141
142!
143!--    Here the user-defined actions follow
144       SELECT CASE ( location )
145
146          CASE ( 'u-tendency' )
147!
148!--          Enter actions to be done in the u-tendency term here
149
150
151          CASE ( 'v-tendency' )
152
153
154          CASE ( 'w-tendency' )
155
156
157          CASE ( 'pt-tendency' )
158
159
160          CASE ( 'sa-tendency' )
161
162
163          CASE ( 'e-tendency' )
164
165
166          CASE ( 'q-tendency' )
167
168
169          CASE ( 'before_timestep', 'after_integration', 'after_timestep' )
170             message_string = 'location "' // location // '" is not ' // &
171                             'allowed to be called with parameters "i" and "j"'
172             CALL message( 'user_actions', 'UI0002', 1, 2, 0, 6, 0 )
173
174
175          CASE DEFAULT
176             message_string = 'unknown location "' // location // '"'
177             CALL message( 'user_actions', 'UI0001', 1, 2, 0, 6, 0 )
178             
179
180       END SELECT
181
182    END SUBROUTINE user_actions_ij
183
184 END MODULE user_actions_mod
Note: See TracBrowser for help on using the repository browser.