/[MITgcm]/MITgcm/pkg/runclock/runclock_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/runclock/runclock_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Tue Jun 30 20:46:10 2009 UTC (14 years, 10 months ago) by ce107
Branch: MAIN
CVS Tags: checkpoint64x, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +2 -2 lines
Fix I descriptor so that gfortran 4.4 doesn't choke on it. Assume that
no more than 9999999 seconds wallclock time limit would ever be asked.

1 ce107 1.2 C $Header: /u/gcmpack/MITgcm/pkg/runclock/runclock_readparms.F,v 1.1 2005/05/31 18:24:34 adcroft Exp $
2 adcroft 1.1 C $Name: $
3    
4     #include "RUNCLOCK_OPTIONS.h"
5    
6     SUBROUTINE RUNCLOCK_READPARMS( myThid )
7     C /==========================================================\
8     C | SUBROUTINE RUNCLOCK_READPARMS |
9     C | o Routine to initialize GM/Redi variables and constants. |
10     C |==========================================================|
11     C \==========================================================/
12     IMPLICIT NONE
13    
14     C === Global variables ===
15     #include "EEPARAMS.h"
16     #include "RUNCLOCK.h"
17    
18     C === Routine arguments ===
19     INTEGER myThid
20    
21     #ifdef ALLOW_RUNCLOCK
22    
23     C-- RUNCLOCK parameters
24     NAMELIST /RUNCLOCK/
25     & RC_maxtime_hr,
26     & RC_maxtime_mi,
27     & RC_maxtime_sc
28    
29     C === Local variables ===
30     C msgBuf - Informational/error meesage buffer
31     CHARACTER*(MAX_LEN_MBUF) msgBuf
32     INTEGER iUnit
33     INTEGER tSecs
34    
35     RUNCLOCKIsOn=.TRUE.
36    
37     _BEGIN_MASTER(myThid)
38    
39     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: opening data.runclock'
40     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
41     & SQUEEZE_RIGHT , 1)
42    
43     CALL OPEN_COPY_DATA_FILE(
44     I 'data.runclock', 'RUNCLOCK_READPARMS',
45     O iUnit,
46     I myThid )
47    
48     C-- Default values for RUNCLOCK
49     RC_maxtime_hr=0
50     RC_maxtime_mi=0
51     RC_maxtime_sc=0
52    
53     C-- Read parameters from open data file
54     READ(UNIT=iUnit,NML=RUNCLOCK)
55    
56     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: read data.runclock done'
57     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
58     & SQUEEZE_RIGHT , 1)
59    
60     C-- Close the open data file
61     CLOSE(iUnit)
62    
63     IF (RC_maxtime_hr.LT.0) THEN
64     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: ERR! RC_maxtime_hr<0'
65     CALL PRINT_ERROR( msgBuf, myThid )
66     ENDIF
67     IF (RC_maxtime_mi.LT.0) THEN
68     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: ERR! RC_maxtime_mi<0'
69     CALL PRINT_ERROR( msgBuf, myThid )
70     ENDIF
71     IF (RC_maxtime_sc.LT.0) THEN
72     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: ERR! RC_maxtime_sc<0'
73     CALL PRINT_ERROR( msgBuf, myThid )
74     ENDIF
75     IF (RC_maxtime_sc.GT.59 .AND. RC_maxtime_mi.NE.0) THEN
76     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: ERR! RC_maxtime_sc>59'
77     CALL PRINT_ERROR( msgBuf, myThid )
78     ENDIF
79     IF (RC_maxtime_mi.GT.59 .AND. RC_maxtime_hr.NE.0) THEN
80     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: ERR! RC_maxtime_mi>59'
81     CALL PRINT_ERROR( msgBuf, myThid )
82     ENDIF
83    
84     tSecs=(RC_maxtime_hr*60+RC_maxtime_mi)*60+RC_maxtime_sc
85     IF (tSecs.EQ.0) THEN
86     WRITE(msgBuf,'(A)') ' RUNCLOCK_READPARMS: no Wall Clock limit set'
87     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
88     & SQUEEZE_RIGHT , 1)
89     c write(0,*) ' RUNCLOCK_READPARMS: no Wall Clock limit set'
90     ELSE
91 ce107 1.2 WRITE(msgBuf,'(A,I7)')
92 adcroft 1.1 & ' RUNCLOCK_READPARMS: Wall Clock limit set to ',tSecs
93     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
94     & SQUEEZE_RIGHT , 1)
95     c write(0,*) ' RUNCLOCK_READPARMS: Wall Clock limit set to ',tSecs
96     ENDIF
97    
98     _END_MASTER(myThid)
99    
100     C-- Everyone else must wait for the parameters to be loaded
101     _BARRIER
102    
103     #endif /* ALLOW_RUNCLOCK */
104    
105     RETURN
106     END

  ViewVC Help
Powered by ViewVC 1.1.22