/[MITgcm]/MITgcm/pkg/rbcs/rbcs_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/rbcs/rbcs_readparms.F

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


Revision 1.8 - (show annotations) (download)
Sat May 14 19:52:12 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62z, checkpoint62y
Changes since 1.7: +46 -6 lines
- split RBCS.h into 3 files: RBCS_SIZE.h  RBCS_PARAMS.h  RBCS_FIELDS.h
- add capability to apply relaxation to horizontal velocity uVel & vVel

1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_readparms.F,v 1.7 2010/11/10 00:34:21 jahn Exp $
2 C $Name: $
3
4 #include "RBCS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: RBCS_READPARMS
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE RBCS_READPARMS( myThid )
11
12 C !DESCRIPTION:
13 C Initialize RBCS parameters, read in data.rbcs
14
15 C !USES: ===============================================================
16 IMPLICIT NONE
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #ifdef ALLOW_PTRACERS
21 #include "PTRACERS_SIZE.h"
22 #endif
23 #include "RBCS_SIZE.h"
24 #include "RBCS_PARAMS.h"
25
26 C !INPUT PARAMETERS: ===================================================
27 C myThid :: my thread Id. number
28 INTEGER myThid
29
30 C !OUTPUT PARAMETERS: ==================================================
31 C none
32
33 #ifdef ALLOW_RBCS
34
35 C === Local variables ===
36 C msgBuf :: Informational/error message buffer
37 C iUnit :: Work variable for IO unit number
38 CHARACTER*(MAX_LEN_MBUF) msgBuf
39 INTEGER iUnit
40 INTEGER irbc
41 #ifdef ALLOW_PTRACERS
42 INTEGER iTracer
43 #endif
44 C-- useRBCptracers is no longer used
45 LOGICAL useRBCptracers
46 CEOP
47
48 C-- RBCS parameters:
49 NAMELIST /RBCS_PARM01/
50 & tauRelaxU,
51 & tauRelaxV,
52 & tauRelaxT,
53 & tauRelaxS,
54 & relaxMaskUFile,
55 & relaxMaskVFile,
56 & relaxMaskFile,
57 & relaxTFile,
58 & relaxSFile,
59 & useRBCuVel,
60 & useRBCvVel,
61 & useRBCtemp,
62 & useRBCsalt,
63 & useRBCptracers,
64 & rbcsIniter,
65 & rbcsForcingPeriod,
66 & rbcsForcingCycle,
67 & rbcsForcingOffset,
68 & rbcsSingleTimeFiles,
69 & deltaTrbcs,
70 & rbcsIter0
71
72 #ifdef ALLOW_PTRACERS
73 NAMELIST /RBCS_PARM02/
74 & useRBCptrnum, tauRelaxPTR,
75 & relaxPtracerFile
76 #endif
77
78 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
79
80 _BEGIN_MASTER(myThid)
81
82 C-- Default values
83 useRBCuVel =.FALSE.
84 useRBCvVel =.FALSE.
85 useRBCtemp =.FALSE.
86 useRBCsalt =.FALSE.
87 tauRelaxU = 0.
88 tauRelaxV = 0.
89 tauRelaxT = 0.
90 tauRelaxS = 0.
91 relaxMaskUFile = ' '
92 relaxMaskVFile = ' '
93 DO irbc=1,maskLEN
94 relaxMaskFile(irbc) = ' '
95 ENDDO
96 relaxUFile = ' '
97 relaxVFile = ' '
98 relaxTFile = ' '
99 relaxSFile = ' '
100 rbcsIniter = 0
101 rbcsForcingPeriod = 0. _d 0
102 rbcsForcingCycle = 0. _d 0
103 rbcsForcingOffset = 0. _d 0
104 rbcsSingleTimeFiles = .FALSE.
105 deltaTrbcs = deltaTclock
106 rbcsIter0 = 0
107 #ifdef ALLOW_PTRACERS
108 DO iTracer=1,PTRACERS_num
109 useRBCptrnum(iTracer)=.FALSE.
110 tauRelaxPTR(iTracer) = 0.
111 relaxPtracerFile(iTracer) = ' '
112 ENDDO
113 #endif
114 useRBCptracers=.FALSE.
115
116 C-- Open and read the data.rbcs file
117
118 WRITE(msgBuf,'(A)') ' RBCS_READPARMS: opening data.rbcs'
119 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
120 & SQUEEZE_RIGHT , 1)
121 CALL OPEN_COPY_DATA_FILE(
122 I 'data.rbcs', 'RBCS_READPARMS',
123 O iUnit,
124 I myThid )
125 READ(UNIT=iUnit,NML=RBCS_PARM01)
126 #ifdef ALLOW_PTRACERS
127 READ(UNIT=iUnit,NML=RBCS_PARM02)
128 #endif
129 WRITE(msgBuf,'(A)')
130 & ' RBCS_READPARMS: finished reading data.rbcs'
131 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
132 & SQUEEZE_RIGHT , 1)
133
134 C-- Close the open data file
135 CLOSE(iUnit)
136
137 C--- Check RBCS config and params:
138 #ifdef DISABLE_RBCS_MOM
139 IF ( useRBCuVel .OR. useRBCvVel ) THEN
140 WRITE(msgBuf,'(2A,2(L2,A))') 'RBCS_READPARMS: ',
141 & 'cannot use RBC for U,V (useRBCuVel=',useRBCuVel,
142 & ', useRBCvVel=',useRBCvVel,')'
143 CALL PRINT_ERROR( msgBuf, myThid )
144 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
145 & 'when DISABLE_RBCS_MOM is defined (in RBCS_OPTIONS.h)'
146 CALL PRINT_ERROR( msgBuf, myThid )
147 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
148 ENDIF
149 #endif /* DISABLE_RBCS_MOM */
150 IF (rbcsIniter.NE.0) THEN
151 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
152 & 'rbcsIniter has been replaced by rbcsForcingOffset '
153 CALL PRINT_ERROR( msgBuf, myThid )
154 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
155 & 'which is in seconds. Please change your data.rbcs'
156 CALL PRINT_ERROR( msgBuf, myThid )
157 STOP 'ABNORMAL END: S/R RBCS_READPARAMS'
158 ENDIF
159 IF (startTime.LT.rbcsForcingOffset+0.5*rbcsForcingPeriod .AND.
160 & .NOT. rbcsSingleTimeFiles) THEN
161 IF (rbcsForcingCycle.GT.0) THEN
162 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
163 & 'startTime before rbcsForcingOffset+0.5*rbcsForcingPeriod '
164 CALL PRINT_ERROR( msgBuf, myThid )
165 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
166 & 'will use last record'
167 CALL PRINT_ERROR( msgBuf, myThid )
168 ELSE
169 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
170 & 'startTime before rbcsForcingOffset+0.5*rbcsForcingPeriod '
171 CALL PRINT_ERROR( msgBuf, myThid )
172 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
173 & 'not allowed with rbcsForcingCycle=0 unless rbcsSingleTimeFiles'
174 CALL PRINT_ERROR( msgBuf, myThid )
175 STOP 'ABNORMAL END: S/R RBCS_READPARAMS'
176 ENDIF
177 ENDIF
178 IF ( useRBCuVel .AND. tauRelaxU.LE.0. ) THEN
179 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
180 & 'tauRelaxU cannot be zero with useRBCuVel'
181 CALL PRINT_ERROR( msgBuf, myThid )
182 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
183 ENDIF
184 IF ( useRBCvVel .AND. tauRelaxV.LE.0. ) THEN
185 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
186 & 'tauRelaxV cannot be zero with useRBCvVel'
187 CALL PRINT_ERROR( msgBuf, myThid )
188 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
189 ENDIF
190 IF ( useRBCtemp .AND. tauRelaxT.LE.0. ) THEN
191 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
192 & 'tauRelaxT cannot be zero with useRBCtemp'
193 CALL PRINT_ERROR( msgBuf, myThid )
194 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
195 ENDIF
196 IF ( useRBCsalt .AND. tauRelaxS.LE.0. ) THEN
197 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
198 & 'tauRelaxS cannot be zero with useRBCsalt'
199 CALL PRINT_ERROR( msgBuf, myThid )
200 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
201 ENDIF
202 #ifdef ALLOW_PTRACERS
203 DO iTracer=1,PTRACERS_num
204 IF ( useRBCptrnum(iTracer) ) THEN
205 IF ( .NOT.usePTRACERS ) THEN
206 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
207 & 'usePTRACERS=F => cannot use RBCS for tracer:', iTracer
208 CALL PRINT_ERROR( msgBuf, myThid )
209 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
210 ENDIF
211 c IF ( iTracer.GT.PTRACERS_numInUse ) THEN
212 c STOP 'ABNORMAL END: S/R RBCS_READPARMS'
213 c ENDIF
214 IF ( tauRelaxPTR(iTracer).LE.0. ) THEN
215 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
216 & 'tauRelaxPTR(itr=', iTracer, ' ) = 0. is'
217 CALL PRINT_ERROR( msgBuf, myThid )
218 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
219 & 'not allowed with useRBCptr(itr)=T'
220 CALL PRINT_ERROR( msgBuf, myThid )
221 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
222 ENDIF
223 ENDIF
224 ENDDO
225 #endif
226 _END_MASTER(myThid)
227
228 C Everyone else must wait for the parameters to be loaded
229 _BARRIER
230
231 #endif /* ALLOW_RBCS */
232
233 RETURN
234 END

  ViewVC Help
Powered by ViewVC 1.1.22