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

Contents of /MITgcm/pkg/gchem/gchem_readparms.F

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


Revision 1.13 - (show annotations) (download)
Tue Apr 8 16:20:16 2008 UTC (16 years, 1 month ago) by dfer
Branch: MAIN
Changes since 1.12: +7 -1 lines
Modifying the calls following rearrangements in pkg dic

1 C $Header: /u/gcmpack/MITgcm/pkg/gchem/gchem_readparms.F,v 1.12 2008/04/06 20:49:03 jmc Exp $
2 C $Name: $
3
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 NAMELIST /GCHEM_PARM01/
44 & tIter0,
45 & WindFile,
46 & IceFile,
47 & AtmospFile,
48 & IronFile,
49 & SilicaFile,
50 & Filename1,
51 & Filename2,
52 & Filename3,
53 & Filename4,
54 & Filename5,
55 & nsubtime,
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 & gchem_ForcingPeriod, gchem_ForcingCycle
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 _BEGIN_MASTER(myThid)
65
66 C Set defaults values for parameters in GCHEM.h
67 useDIC = .FALSE.
68 useCFC = .FALSE.
69 tIter0 = UNSET_I
70 nsubtime=1
71 windFile=' '
72 atmospFile=' '
73 IceFile=' '
74 IronFile=' '
75 SilicaFile=' '
76 Filename1=' '
77 Filename2=' '
78 Filename3=' '
79 Filename4=' '
80 Filename5=' '
81 gchem_int1=0
82 gchem_int2=0
83 gchem_int3=0
84 gchem_int4=0
85 gchem_int5=0
86 gchem_rl1=0. _d 0
87 gchem_rl2=0. _d 0
88 gchem_rl3=0. _d 0
89 gchem_rl4=0. _d 0
90 gchem_rl5=0. _d 0
91 c default periodic forcing to same as for physics
92 gchem_ForcingPeriod=externForcingPeriod
93 gchem_ForcingCycle=externForcingCycle
94 C Open and read the data.gchem file
95 WRITE(msgBuf,'(A)') ' GCHEM_READPARMS: opening data.gchem'
96 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
97 & SQUEEZE_RIGHT , 1)
98 CALL OPEN_COPY_DATA_FILE(
99 I 'data.gchem', 'GCHEM_PARM01',
100 O iUnit,
101 I myThid )
102 READ(UNIT=iUnit,NML=GCHEM_PARM01)
103 WRITE(msgBuf,'(A)')
104 & ' GCHEM_READPARMS: finished reading data.gchem'
105 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
106 & SQUEEZE_RIGHT , 1)
107
108 C Close the open data file
109 CLOSE(iUnit)
110
111 C- Sub-package on/off flags: until fully implemented, which requires
112 C a) to read the flag value from data.gchem
113 C b) to test the flag before any corresponding pkg S/R call
114 C- (for now) just it turned on when the corresponding pkg is compliled
115 #ifdef ALLOW_DIC
116 useDIC = .TRUE.
117 #endif
118 #ifdef ALLOW_CFC
119 useCFC = .TRUE.
120 #endif
121
122 C- Check for retired parameters:
123 IF ( tIter0 .NE. UNSET_I ) THEN
124 c nRetired = nRetired+1
125 WRITE(msgBuf,'(A,A)')
126 & 'S/R GCHEM_READPARMS: Paramater "tIter0" is',
127 & ' no longer allowed in file "data.gchem"'
128 CALL PRINT_ERROR( msgBuf , myThid)
129 WRITE(msgBuf,'(A,A)')
130 & 'S/R GCHEM_READPARMS: "tIter0" has been moved to',
131 & ' PTRACERS_Iter0 in file "data.ptracers".'
132 CALL PRINT_ERROR( msgBuf , myThid)
133 STOP 'ABNORMAL END: S/R GCHEM_READPARMS'
134 ENDIF
135
136 _END_MASTER(myThid)
137
138 #ifdef ALLOW_DIC
139 IF ( useDIC ) THEN
140 CALL DIC_READPARMS(myThid)
141 ENDIF
142 #endif
143
144 C Everyone else must wait for the parameters to be loaded
145 _BARRIER
146
147 #endif /* ALLOW_GCHEM */
148
149 RETURN
150 END

  ViewVC Help
Powered by ViewVC 1.1.22