/[MITgcm]/MITgcm_contrib/darwin/pkg/gchem/gchem_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin/pkg/gchem/gchem_readparms.F

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


Revision 1.3 - (hide annotations) (download)
Mon Jun 2 20:32:49 2008 UTC (17 years, 1 month ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin_ckpt61i_20090224, ctrb_darwin_ckpt61r_20090626, ctrb_darwin_ckpt61m_20090430, ctrb_darwin_ckpt61d_20081212, ctrb_darwin_ckpt61t_20090820, ctrb_darwin_ckpt59p_20080604, ctrb_darwin_ckpt61v_20091024, ctrb_darwin_ckpt61w_20091024, ctrb_darwin_ckpt61h_20090224, ctrb_darwin_ckpt62a_20100117, ctrb_darwin_ckpt61s_20090630, ctrb_darwin_ckpt61_20080822, ctrb_darwin_ckpt61y_20091120, ctrb_darwin_ckpt61q_20090626, ctrb_darwin_ckpt61_20080624, ctrb_darwin_ckpt61o_20090527, ctrb_darwin_ckpt61d_20081013, ctrb_darwin_ckpt61k_20090312, ctrb_darwin_ckpt61i_20090312, ctrb_darwin_ckpt62_20091227, ctrb_darwin_ckpt59q_20080605, ctrb_darwin_ckpt61o_20090610, ctrb_darwin_ckpt61x_20091024, ctrb_darwin_ckpt61p_20090610, ctrb_darwin_ckpt61b_20080822, ctrb_darwin_ckpt61u_20090825, ctrb_darwin_ckpt61l_20090408, ctrb_darwin_ckpt62b_20100201, ctrb_darwin_ckpt61z_20091207, ctrb_darwin_ckpt62c_20100303, ctrb_darwin_ckpt59r_20080606, ctrb_darwin_ckpt61n_20090519, ctrb_darwin_ckpt60_20080619, ctrb_darwin_ckpt61n_20090513
Changes since 1.2: +36 -16 lines
upgrade to MITgcm checkpoint59p (move darwin params to data.darwin)

1 jahn 1.3 C $Header$
2     C $Name$
3 jahn 1.1
4     #include "GCHEM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: GCHEM_READPARMS
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE GCHEM_READPARMS( myThid )
11    
12     C !DESCRIPTION:
13     C Initialize GCHEM parameters, read in data.gchem
14    
15     C !USES: ===============================================================
16     IMPLICIT NONE
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "GCHEM.h"
21    
22     C !INPUT PARAMETERS: ===================================================
23     C myThid :: thread number
24     INTEGER myThid
25    
26     C !OUTPUT PARAMETERS: ==================================================
27     C none
28    
29     #ifdef ALLOW_GCHEM
30    
31     C !LOCAL VARIABLES: ====================================================
32     C tIter0 :: retired parameter
33     C iTracer :: loop indices
34     C iUnit :: unit number for I/O
35     C msgBuf :: message buffer
36     INTEGER tIter0
37     INTEGER iTracer
38     INTEGER iUnit
39     CHARACTER*(MAX_LEN_MBUF) msgBuf
40     c PARAMETER ( UNSET_I = 123456789 )
41     CEOP
42    
43 jahn 1.3 C- Sub-package on/off flags: not fully implemented, requires
44     C to test the flag before any corresponding pkg S/R call
45    
46 jahn 1.1 NAMELIST /GCHEM_PARM01/
47 jahn 1.3 & nsubtime,
48     & useDIC,
49     & useCFC,
50     & useDARWIN,
51 jahn 1.1 & Filename1,
52     & Filename2,
53     & Filename3,
54     & Filename4,
55     & Filename5,
56     & gchem_int1, gchem_int2, gchem_int3,
57     & gchem_int4, gchem_int5,
58     & gchem_rl1, gchem_rl2, gchem_rl3,
59     & gchem_rl4, gchem_rl5,
60 jahn 1.3 & gchem_ForcingPeriod, gchem_ForcingCycle,
61     & tIter0
62    
63     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64    
65     _BEGIN_MASTER(myThid)
66 jahn 1.1
67     C Set defaults values for parameters in GCHEM.h
68 jahn 1.3 useDIC = .FALSE.
69     useCFC = .FALSE.
70     useDARWIN = .FALSE.
71 jahn 1.1 tIter0 = UNSET_I
72     nsubtime=1
73     Filename1=' '
74     Filename2=' '
75     Filename3=' '
76     Filename4=' '
77     Filename5=' '
78     gchem_int1=0
79     gchem_int2=0
80     gchem_int3=0
81     gchem_int4=0
82     gchem_int5=0
83 jahn 1.2 gchem_rl1=0. _d 0
84     gchem_rl2=0. _d 0
85     gchem_rl3=0. _d 0
86     gchem_rl4=0. _d 0
87     gchem_rl5=0. _d 0
88 jahn 1.1 c default periodic forcing to same as for physics
89     gchem_ForcingPeriod=externForcingPeriod
90     gchem_ForcingCycle=externForcingCycle
91     C Open and read the data.gchem file
92     WRITE(msgBuf,'(A)') ' GCHEM_READPARMS: opening data.gchem'
93     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
94     & SQUEEZE_RIGHT , 1)
95     CALL OPEN_COPY_DATA_FILE(
96     I 'data.gchem', 'GCHEM_PARM01',
97     O iUnit,
98     I myThid )
99     READ(UNIT=iUnit,NML=GCHEM_PARM01)
100     WRITE(msgBuf,'(A)')
101     & ' GCHEM_READPARMS: finished reading data.gchem'
102     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
103     & SQUEEZE_RIGHT , 1)
104    
105     C Close the open data file
106     CLOSE(iUnit)
107    
108     C- Check for retired parameters:
109     IF ( tIter0 .NE. UNSET_I ) THEN
110     c nRetired = nRetired+1
111     WRITE(msgBuf,'(A,A)')
112     & 'S/R GCHEM_READPARMS: Paramater "tIter0" is',
113     & ' no longer allowed in file "data.gchem"'
114     CALL PRINT_ERROR( msgBuf , myThid)
115     WRITE(msgBuf,'(A,A)')
116     & 'S/R GCHEM_READPARMS: "tIter0" has been moved to',
117     & ' PTRACERS_Iter0 in file "data.ptracers".'
118     CALL PRINT_ERROR( msgBuf , myThid)
119     STOP 'ABNORMAL END: S/R GCHEM_READPARMS'
120     ENDIF
121    
122     _END_MASTER(myThid)
123    
124     C Everyone else must wait for the parameters to be loaded
125     _BARRIER
126    
127 jahn 1.3 #ifdef ALLOW_DIC
128     IF ( useDIC ) THEN
129     CALL DIC_READPARMS(myThid)
130     ENDIF
131     #endif
132    
133     #ifdef ALLOW_CFC
134     IF ( useCFC ) THEN
135     CALL CFC_READPARMS(myThid)
136     ENDIF
137     #endif
138    
139     #ifdef ALLOW_DARWIN
140     IF ( useDARWIN ) THEN
141     CALL DARWIN_READPARMS(myThid)
142     ENDIF
143     #endif
144    
145 jahn 1.1 #endif /* ALLOW_GCHEM */
146    
147     RETURN
148     END

  ViewVC Help
Powered by ViewVC 1.1.22