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

Last change on this file since 247 was 226, checked in by raasch, 15 years ago

preparations for the next release

  • Property svn:keywords set to Id
File size: 4.3 KB
Line 
1 MODULE user_actions_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: user_actions.f90 226 2009-02-02 07:39:34Z heinze $
11!
12! 211 2008-11-11 04:46:24Z raasch
13! Former file user_interface.f90 split into one file per subroutine
14!
15! Description:
16! ------------
17! Execution of user-defined actions before or after single timesteps
18!------------------------------------------------------------------------------!
19
20    PRIVATE
21    PUBLIC user_actions
22
23    INTERFACE user_actions
24       MODULE PROCEDURE user_actions
25       MODULE PROCEDURE user_actions_ij
26    END INTERFACE user_actions
27
28 CONTAINS
29
30
31!------------------------------------------------------------------------------!
32! Call for all grid points
33!------------------------------------------------------------------------------!
34    SUBROUTINE user_actions( location )
35
36       USE control_parameters
37       USE cpulog
38       USE indices
39       USE interfaces
40       USE pegrid
41       USE user
42       USE arrays_3d
43
44       IMPLICIT NONE
45
46       CHARACTER (LEN=*) ::  location
47
48       INTEGER ::  i, j, k
49
50       CALL cpu_log( log_point(24), 'user_actions', 'start' )
51
52!
53!--    Here the user-defined actions follow
54!--    No calls for single grid points are allowed at locations before and
55!--    after the timestep, since these calls are not within an i,j-loop
56       SELECT CASE ( location )
57
58          CASE ( 'before_timestep' )
59!
60!--          Enter actions to be done before every timestep here
61
62
63          CASE ( 'after_integration' )
64!
65!--          Enter actions to be done after every time integration (before
66!--          data output)
67!--          Sample for user-defined output:
68!             DO  i = nxl-1, nxr+1
69!                DO  j = nys-1, nyn+1
70!                   DO  k = nzb, nzt+1
71!                      u2(k,j,i) = u(k,j,i)**2
72!                   ENDDO
73!                ENDDO
74!             ENDDO
75!             DO  i = nxl-1, nxr
76!                DO  j = nys-1, nyn
77!                   DO  k = nzb, nzt+1
78!                      ustvst(k,j,i) =  &
79!                         ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
80!                         ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
81!                   ENDDO
82!                ENDDO
83!             ENDDO
84
85
86          CASE ( 'after_timestep' )
87!
88!--          Enter actions to be done after every timestep here
89
90
91          CASE ( 'u-tendency' )
92!
93!--          Enter actions to be done in the u-tendency term here
94
95
96          CASE ( 'v-tendency' )
97
98
99          CASE ( 'w-tendency' )
100
101
102          CASE ( 'pt-tendency' )
103
104
105          CASE ( 'sa-tendency' )
106
107
108          CASE ( 'e-tendency' )
109
110
111          CASE ( 'q-tendency' )
112
113
114          CASE DEFAULT
115             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
116                                       location, '"'
117             CALL local_stop
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             IF ( myid == 0 )  THEN
171                PRINT*, '+++ user_actions: location "', location, '" is not ', &
172                             'allowed to be called with parameters "i" and "j"'
173             ENDIF
174             CALL local_stop
175
176
177          CASE DEFAULT
178             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
179                                       location, '"'
180             CALL local_stop
181
182
183       END SELECT
184
185    END SUBROUTINE user_actions_ij
186
187 END MODULE user_actions_mod
Note: See TracBrowser for help on using the repository browser.