source: palm/trunk/SOURCE/check_for_restart.f90 @ 199

Last change on this file since 199 was 110, checked in by raasch, 16 years ago

New:
---
Allows runs for a coupled atmosphere-ocean LES,
coupling frequency is controlled by new d3par-parameter dt_coupling,
the coupling mode (atmosphere_to_ocean or ocean_to_atmosphere) for the
respective processes is read from environment variable coupling_mode,
which is set by the mpiexec-command,
communication between the two models is done using the intercommunicator
comm_inter,
local files opened by the ocean model get the additional suffic "_O".
Assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean.

A momentum flux can be set as top boundary condition using the new
inipar parameter top_momentumflux_u|v.

Non-cyclic boundary conditions can be used along all horizontal directions.

Quantities w*p* and w"e can be output as vertical profiles.

Initial profiles are reset to constant profiles in case that initializing_actions /= 'set_constant_profiles'. (init_rankine)

Optionally calculate km and kh from initial TKE e_init.

Changed:


Remaining variables iran changed to iran_part (advec_particles, init_particles).

In case that the presure solver is not called for every Runge-Kutta substep
(call_psolver_at_all_substeps = .F.), it is called after the first substep
instead of the last. In that case, random perturbations are also added to the
velocity field after the first substep.

Initialization of km,kh = 0.00001 for ocean = .T. (for ocean = .F. it remains 0.01).

Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T. (instead of cloud_physics = .T.).

Errors:


Bugs from code parts for non-cyclic boundary conditions are removed: loops for
u and v are starting from index nxlu, nysv, respectively. The radiation boundary
condition is used for every Runge-Kutta substep. Velocity phase speeds for
the radiation boundary conditions are calculated for the first Runge-Kutta
substep only and reused for the further substeps. New arrays c_u, c_v, and c_w
are defined for this purpose. Several index errors are removed from the
radiation boundary condition code parts. Upper bounds for calculating
u_0 and v_0 (in production_e) are nxr+1 and nyn+1 because otherwise these
values are not available in case of non-cyclic boundary conditions.

+dots_num_palm in module user, +module netcdf_control in user_init (both in user_interface)

Bugfix: wrong sign removed from the buoyancy production term in the case use_reference = .T. (production_e)

Bugfix: Error message concerning output of particle concentration (pc) modified (check_parameters).

Bugfix: Rayleigh damping for ocean fixed.

  • Property svn:keywords set to Id
File size: 4.7 KB
Line 
1 SUBROUTINE check_for_restart
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: check_for_restart.f90 110 2007-10-05 05:13:14Z raasch $
11!
12! 108 2007-08-24 15:10:38Z letzel
13! modifications to terminate coupled runs
14!
15! RCS Log replace by Id keyword, revision history cleaned up
16!
17! Revision 1.11  2007/02/11 12:55:13  raasch
18! Informative output to the job protocol
19!
20! Revision 1.1  1998/03/18 20:06:51  raasch
21! Initial revision
22!
23!
24! Description:
25! ------------
26! Set stop flag, if restart is neccessary because of expiring cpu-time or
27! if it is forced by user
28!------------------------------------------------------------------------------!
29
30    USE pegrid
31    USE control_parameters
32
33    IMPLICIT NONE
34
35
36    LOGICAL :: terminate_run_l
37    REAL ::  remaining_time
38
39
40!
41!-- Check remaining CPU-time
42    CALL local_tremain( remaining_time )
43
44!
45!-- If necessary set a flag to stop the model run
46    terminate_run_l = .FALSE.
47    IF ( remaining_time <= termination_time_needed  .AND. &
48         write_binary(1:4) == 'true' )  THEN
49
50       terminate_run_l = .TRUE.
51    ENDIF
52
53#if defined( __parallel )
54!
55!-- Make a logical OR for all processes. Stop the model run if at least
56!-- one processor has reached the time limit.
57    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, &
58                        MPI_LOR, comm2d, ierr )
59#else
60    terminate_run = terminate_run_l
61#endif
62
63!
64!-- Output that job will be terminated
65    IF ( terminate_run  .AND.  myid == 0 )  THEN
66       PRINT*, '*** WARNING: run will be terminated because it is running out', &
67                    ' of job cpu limit'
68       PRINT*, '             remaining time:         ', remaining_time, ' s'
69       PRINT*, '             termination time needed:', termination_time_needed,&
70                    ' s'
71    ENDIF
72
73!
74!-- In case of coupled runs inform the remote model of the termination
75!-- and its reason, provided the remote model has not already been
76!-- informed of another termination reason (terminate_coupled > 0) before,
77!-- or vice versa (terminate_coupled_remote > 0).
78    IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND. &
79         terminate_coupled == 0  .AND.  terminate_coupled_remote == 0 )  THEN
80
81       terminate_coupled = 3
82       CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER, myid,  0, &
83                          terminate_coupled_remote, 1, MPI_INTEGER, myid,  0, &
84                          comm_inter, status, ierr )
85    ENDIF
86
87!
88!-- Set the stop flag also, if restart is forced by user
89    IF ( time_restart /= 9999999.9  .AND.  time_restart < simulated_time ) &
90    THEN
91!
92!--    Restart is not neccessary, if the end time of the run (given by
93!--    the user) has been reached
94       IF ( simulated_time < end_time )  THEN
95          terminate_run = .TRUE.
96!
97!--       Increment restart time, if forced by user, otherwise set restart
98!--       time to default (no user restart)
99          IF ( dt_restart /= 9999999.9 )  THEN
100             time_restart = time_restart + dt_restart
101          ELSE
102             time_restart = 9999999.9
103          ENDIF
104
105          IF ( myid == 0 )  THEN
106             PRINT*, '*** INFORMATIVE: run will be terminated due to user ', &
107                                       'settings of'
108             PRINT*, '                 restart_time / dt_restart'
109             PRINT*, '                 new restart time is: ', time_restart, ' s'
110          ENDIF
111!
112!--       In case of coupled runs inform the remote model of the termination
113!--       and its reason, provided the remote model has not already been
114!--       informed of another termination reason (terminate_coupled > 0) before,
115!--       or vice versa (terminate_coupled_remote > 0).
116          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0  .AND. &
117               terminate_coupled_remote == 0)  THEN
118
119             IF ( dt_restart /= 9999999.9 )  THEN
120                terminate_coupled = 4
121             ELSE
122                terminate_coupled = 5
123             ENDIF
124             CALL MPI_SENDRECV(                                                 &
125                            terminate_coupled,        1, MPI_INTEGER, myid,  0, &
126                            terminate_coupled_remote, 1, MPI_INTEGER, myid,  0, &
127                            comm_inter, status, ierr )
128          ENDIF
129       ELSE
130          time_restart = 9999999.9
131       ENDIF
132    ENDIF
133
134!
135!-- If the run is stopped, set a flag file which is necessary to initiate
136!-- the start of a continuation run
137    IF ( terminate_run  .AND.  myid == 0 )  THEN
138
139       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
140       WRITE ( 90, '(A)' )  TRIM( run_description_header )
141       CLOSE ( 90 )
142
143    ENDIF
144
145
146 END SUBROUTINE check_for_restart
Note: See TracBrowser for help on using the repository browser.