source: palm/tags/release-3.2b/SOURCE/run_control.f90 @ 3999

Last change on this file since 3999 was 90, checked in by raasch, 17 years ago

New:
---
Calculation and output of user-defined profiles. New &userpar parameters data_output_pr_user and max_pr_user.

check_parameters, flow_statistics, modules, parin, read_var_list, user_interface, write_var_list

Changed:


Division through dt_3d replaced by multiplication of the inverse. For performance optimisation, this is done in the loop calculating the divergence instead of using a seperate loop. (pres.f90) var_hom and var_sum renamed pr_palm.

data_output_profiles, flow_statistics, init_3d_model, modules, parin, pres, read_var_list, run_control, time_integration

Errors:


Bugfix: work_fft*_vec removed from some PRIVATE-declarations (poisfft).

Bugfix: field_chr renamed field_char (user_interface).

Bugfix: output of use_upstream_for_tke (header).

header, poisfft, user_interface

  • Property svn:keywords set to Id
File size: 4.1 KB
Line 
1 SUBROUTINE run_control
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: run_control.f90 90 2007-05-30 09:18:47Z suehring $
11!
12! 87 2007-05-22 15:46:47Z raasch
13! var_hom renamed pr_palm
14!
15! 82 2007-04-16 15:40:52Z raasch
16! Preprocessor strings for different linux clusters changed to "lc",
17! routine local_flush is used for buffer flushing
18!
19! RCS Log replace by Id keyword, revision history cleaned up
20!
21! Revision 1.20  2006/06/02 15:23:47  raasch
22! cpp-directives extended for lctit
23!
24! Revision 1.1  1997/08/11 06:25:38  raasch
25! Initial revision
26!
27!
28! Description:
29! ------------
30! Computation and output of run-control quantities
31!------------------------------------------------------------------------------!
32
33    USE cpulog
34    USE indices
35    USE interfaces
36    USE pegrid
37    USE statistics
38    USE control_parameters
39
40    IMPLICIT NONE
41
42    CHARACTER (LEN=1) ::  change_chr, disturb_chr
43
44!
45!-- If required, do statistics
46    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
47
48!
49!-- Flow_statistics has its own cpu-time measurement
50    CALL cpu_log( log_point(11), 'run_control', 'start' )
51
52!
53!-- Output
54    IF ( myid == 0 )  THEN
55
56!
57!--    Check, whether file unit is already open (may have been opened in header
58!--    before)
59       CALL check_open( 15 )
60
61!
62!--    If required, write header
63       IF ( .NOT. run_control_header )  THEN
64          WRITE ( 15, 100 )
65          run_control_header = .TRUE.
66       ENDIF
67
68!
69!--    Output the the beginning of the run receives no information about an
70!--    Euler-timestep
71       IF ( dt_changed  .AND.  simulated_time /= 0.0  .AND. &
72            timestep_scheme(1:5) /= 'runge' )  THEN
73          IF ( timestep_scheme == 'leapfrog' )  THEN
74             change_chr = 'L'
75          ELSE
76             change_chr = 'E'
77          ENDIF
78       ELSE
79          change_chr = ' '
80       ENDIF
81!
82!--    If required, set disturbance flag
83       IF ( disturbance_created )  THEN
84          disturb_chr = 'D'
85       ELSE
86          disturb_chr = ' '
87       ENDIF
88       WRITE ( 15, 101 )  runnr, current_timestep_number, simulated_time_chr,  &
89                          simulated_time-INT( simulated_time ), dt_3d,         &
90                          timestep_reason, change_chr, u_max, disturb_chr,     &
91                          v_max, disturb_chr, w_max, hom(nzb,1,pr_palm,0),     &
92                          hom(nzb+8,1,pr_palm,0), hom(nzb+3,1,pr_palm,0),      &
93                          hom(nzb+6,1,pr_palm,0), hom(nzb+4,1,pr_palm,0),      &
94                          hom(nzb+5,1,pr_palm,0), hom(nzb+9,1,pr_palm,0),      &
95                          hom(nzb+10,1,pr_palm,0), u_max_ijk(1:3),             &
96                          v_max_ijk(1:3), w_max_ijk(1:3),                      &
97                          advected_distance_x/1000.0,                          &
98                          advected_distance_y/1000.0, mgcycles
99!
100!--    Write buffer contents to disc immediately
101       CALL local_flush( 15 )
102
103    ENDIF
104!
105!-- If required, reset disturbance flag. This has to be done outside the above
106!-- IF-loop, because the flag would otherwise only be reset on PE0
107    IF ( disturbance_created )  disturbance_created = .FALSE.
108
109    CALL cpu_log( log_point(11), 'run_control', 'stop' )
110
111!
112!-- Formats
113100 FORMAT (///'Run-control output:'/ &
114              &'------------------'// &
115           &'RUN  ITER. HH:MM:SS.SS   DT(E)     UMAX     VMAX     WMAX     U*', &
116           &'    W*   THETA*   Z_I     ENERG.   DISTENERG    DIVOLD     DIVNE', &
117           &'W     UMAX(KJI)    VMAX(KJI)    WMAX(KJI)   ADVECX   ADVECY   MG', &
118           &'CYC'/ &
119           &'----------------------------------------------------------------', &
120           &'----------------------------------------------------------------', &
121           &'----------------------------------------------------------------', &
122           &'--')
123101 FORMAT (I3,1X,I6,1X,A8,F3.2,1X,F7.4,A1,A1,F8.4,A1,F8.4,A1,F8.4,2X,F5.3,2X, &
124            F4.2, &
125            2X,F6.3,2X,F5.0,1X,4(E10.3,1X),3(3(I4),1X),F8.3,1X,F8.3,5X,I3)
126
127 END SUBROUTINE run_control
Note: See TracBrowser for help on using the repository browser.