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

Last change on this file since 212 was 211, checked in by raasch, 15 years ago

user interface was split into one single file per subroutine

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