source: palm/tags/release-3.2a/SOURCE/run_control.f90 @ 336

Last change on this file since 336 was 83, checked in by raasch, 17 years ago

New:
---

Changed:


PALM can be generally installed on any kind of Linux-, IBM-AIX-, or NEC-SX-system by adding appropriate settings to the configuration file.

Scripts are also running under the public domain ksh.

All system relevant compile and link options as well as the host identifier (local_host) are specified in the configuration file.

Filetransfer by ftp removed (options -f removed from mrun and mbuild).

Call of (system-)FLUSH routine moved to new routine local_flush.

return_addres and return_username are read from ENVPAR-NAMELIST-file instead of using local_getenv.

Preprocessor strings for different linux clusters changed to "lc", some preprocessor directives renamed (new: intel_openmp_bug), preprocessor directives for old systems removed

advec_particles, check_open, cpu_log, cpu_statistics, data_output_dvrp, flow_statistics, header, init_dvrp, init_particles, init_1d_model, init_dvrp, init_pegrid, local_getenv, local_system, local_tremain, local_tremain_ini, modules, palm, parin, run_control

new:
local_flush

mbuild, mrun

Errors:


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