/[MITgcm]/MITgcm/model/src/ini_parms.F
ViewVC logotype

Annotation of /MITgcm/model/src/ini_parms.F

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


Revision 1.18 - (hide annotations) (download)
Mon Jun 15 05:13:56 1998 UTC (26 years ago) by cnh
Branch: MAIN
CVS Tags: checkpoint7
Branch point for: checkpoint7-4degree-ref
Changes since 1.17: +27 -13 lines
Fairly coplete 4 degree global intercomparison
setup.
 Includes changes to make convective adjustment and hydrostatic
pressure correct as well as IO for climatological datasets

1 cnh 1.18 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_parms.F,v 1.17 1998/06/12 19:33:33 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     SUBROUTINE INI_PARMS( myThid )
6     C /==========================================================\
7     C | SUBROUTINE INI_PARMS |
8     C | o Routine to set model "parameters" |
9     C |==========================================================|
10     C | Notes: |
11     C | ====== |
12     C | The present version of this routine is a place-holder. |
13     C | A production version needs to handle parameters from an |
14     C | external file and possibly reading in some initial field |
15     C | values. |
16     C \==========================================================/
17    
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "CG2D.h"
23    
24     C === Routine arguments ===
25     C myThid - Number of this instance of INI_PARMS
26     INTEGER myThid
27    
28     C === Local variables ===
29     C dxSpacing, dySpacing - Default spacing in X and Y.
30     C Units are that of coordinate system
31     C i.e. cartesian => metres
32     C s. polar => degrees
33     C goptCount - Used to count the nuber of grid options
34     C (only one is allowed! )
35     C msgBuf - Informational/error meesage buffer
36     C errIO - IO error flag
37     C iUnit - Work variable for IO unit number
38     C record - Work variable for IO buffer
39     C K, I, J - Loop counters
40     REAL dxSpacing
41     REAL dySpacing
42     CHARACTER*(MAX_LEN_MBUF) msgBuf
43     CHARACTER*(MAX_LEN_PREC) record
44     INTEGER goptCount
45     INTEGER K, I, J, IL, iUnit
46     INTEGER errIO
47     INTEGER IFNBLNK
48     EXTERNAL IFNBLNK
49     INTEGER ILNBLNK
50     EXTERNAL ILNBLNK
51    
52     C-- Continuous equation parameters
53     NAMELIST /PARM01/
54 cnh 1.8 & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,
55 cnh 1.1 & viscAh, viscAz, viscA4,
56     & diffKhT, diffKzT, diffK4T,
57     & diffKhS, diffKzS, diffK4S,
58 adcroft 1.6 & GMmaxslope,GMlength,GMalpha,GMdepth,GMkbackground,
59 adcroft 1.11 & tRef, sRef, eosType,
60 cnh 1.1 & momViscosity, momAdvection, momForcing, useCoriolis,
61 cnh 1.14 & momPressureForcing, metricTerms,
62 cnh 1.1 & tempDiffusion, tempAdvection, tempForcing,
63 cnh 1.8 & saltDiffusion, saltAdvection, saltForcing,
64 cnh 1.10 & implicitFreeSurface, rigidLid, freeSurfFac,
65 adcroft 1.16 & tempStepping, saltStepping, momStepping, implicitDiffusion
66 cnh 1.1
67     C-- Elliptic solver parameters
68     NAMELIST /PARM02/
69 cnh 1.7 & cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual, cg2dpcOffDFac
70 cnh 1.1
71     C-- Time stepping parammeters
72     NAMELIST /PARM03/
73 cnh 1.5 & nIter0, nTimeSteps, deltaT, deltaTmom, deltaTtracer, abEps, tauCD, rCD,
74 cnh 1.9 & startTime, endTime, chkPtFreq, dumpFreq, deltaTClock, pChkPtFreq,
75 cnh 1.18 & cAdjFreq, tauThetaClimRelax, tauSaltClimRelax
76 cnh 1.1
77     C-- Gridding parameters
78     NAMELIST /PARM04/
79     & usingCartesianGrid, delZ, dxSpacing, dySpacing, delX, delY,
80     & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
81     & l, m, n
82    
83 cnh 1.15 C-- Input files
84     NAMELIST /PARM05/
85     & bathyFile, hydrogThetaFile, hydrogSaltFile,
86 cnh 1.18 & zonalWindFile, meridWindFile, thetaClimFile,
87     & saltClimFile
88 cnh 1.15
89 cnh 1.1 C
90     _BEGIN_MASTER(myThid)
91    
92     C-- Open the parameter file
93     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
94     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
95     OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',err=1,IOSTAT=errIO)
96     IF ( errIO .GE. 0 ) GOTO 2
97     1 CONTINUE
98     WRITE(msgBuf,'(A)')
99     & 'S/R INI_PARMS'
100     CALL PRINT_ERROR( msgBuf , 1)
101     WRITE(msgBuf,'(A)')
102     & 'Unable to open model parameter'
103     CALL PRINT_ERROR( msgBuf , 1)
104     WRITE(msgBuf,'(A)')
105     & 'file "data"'
106     CALL PRINT_ERROR( msgBuf , 1)
107     CALL MODELDATA_EXAMPLE( myThid )
108     STOP 'ABNORMAL END: S/R INI_PARMS'
109     2 CONTINUE
110    
111     1000 CONTINUE
112     READ(modelDataUnit,FMT='(A)',END=1001) RECORD
113     IL = MAX(ILNBLNK(RECORD),1)
114     IF ( RECORD(1:1) .NE. commentCharacter )
115     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
116     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
117     GOTO 1000
118     1001 CONTINUE
119     CLOSE(modelDataUnit)
120    
121     C-- Report contents of model parameter file
122     WRITE(msgBuf,'(A)')
123     &'// ======================================================='
124     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
125     WRITE(msgBuf,'(A)') '// Model parameter file "data"'
126     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
127     WRITE(msgBuf,'(A)')
128     &'// ======================================================='
129     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
130     & SQUEEZE_RIGHT , 1)
131     iUnit = scrUnit2
132     REWIND(iUnit)
133     2000 CONTINUE
134     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
135     IL = MAX(ILNBLNK(RECORD),1)
136     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
137     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
138     GOTO 2000
139     2001 CONTINUE
140     CLOSE(iUnit)
141     WRITE(msgBuf,'(A)') ' '
142     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
143     & SQUEEZE_RIGHT , 1)
144    
145    
146     C-- Read settings from model parameter file "data".
147     iUnit = scrUnit1
148     REWIND(iUnit)
149    
150     C-- Set default "physical" parameters
151     DO K =1,Nz
152     tRef(K) = 30.D0 - FLOAT(K)
153     ENDDO
154     gravity = 9.81 D0
155 cnh 1.8 gBaro = gravity
156 cnh 1.1 rhoNil = 999.8 D0
157     f0=1.D-4
158     beta = 1. _d -11
159     viscAh=1.d3
160 adcroft 1.16 diffKhT=1.0d3
161     diffKhS=1.0d3
162 cnh 1.1 viscAz=1.d-3
163     diffKzT=1.d-5
164 adcroft 1.16 diffKzS=1.d-5
165     viscA4=0.
166 cnh 1.1 diffK4T=0.
167     diffK4S=0.
168 adcroft 1.6 GMmaxslope=1.d-2
169     GMlength=200.d3
170     GMalpha=0.
171     GMdepth=1000.
172     GMkbackground=0.
173 adcroft 1.11 tAlpha=2.d-4
174 cnh 1.18 sBeta=7.4d-4
175 adcroft 1.13 eosType='LINEAR'
176 cnh 1.8 implicitFreeSurface = .TRUE.
177     rigidLid = .FALSE.
178     freeSurfFac = 1. _d 0
179 cnh 1.9 momViscosity = .TRUE.
180     momAdvection = .TRUE.
181     momForcing = .TRUE.
182     useCoriolis = .TRUE.
183     momPressureForcing = .TRUE.
184 cnh 1.10 momStepping = .TRUE.
185     tempStepping = .TRUE.
186 adcroft 1.16 saltStepping = .TRUE.
187 cnh 1.14 metricTerms = .TRUE.
188 adcroft 1.12 implicitDiffusion = .FALSE.
189 cnh 1.1 READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)
190     IF ( errIO .GE. 0 ) GOTO 4
191     3 CONTINUE
192     WRITE(msgBuf,'(A)')
193     & 'S/R INI_PARMS'
194     CALL PRINT_ERROR( msgBuf , 1)
195     WRITE(msgBuf,'(A)')
196     & 'Error reading numerical model '
197     CALL PRINT_ERROR( msgBuf , 1)
198     WRITE(msgBuf,'(A)')
199     & 'parameter file "data"'
200     CALL PRINT_ERROR( msgBuf , 1)
201     WRITE(msgBuf,'(A)')
202     & 'Problem in namelist PARM01'
203     CALL PRINT_ERROR( msgBuf , 1)
204     CALL MODELDATA_EXAMPLE( myThid )
205     STOP 'ABNORMAL END: S/R INI_PARMS'
206     4 CONTINUE
207 cnh 1.8 IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0
208     IF ( rigidLid ) freeSurfFac = 0. _d 0
209 cnh 1.9 IF ( momViscosity ) THEN
210     vfFacMom = 1. _d 0
211     ELSE
212     vfFacMom = 0. _d 0
213     ENDIF
214     IF ( momAdvection ) THEN
215     afFacMom = 1. _d 0
216     ELSE
217     afFacMom = 0. _d 0
218     ENDIF
219     IF ( momForcing ) THEN
220     foFacMom = 1. _d 0
221     ELSE
222     foFacMom = 0. _d 0
223     ENDIF
224     IF ( useCoriolis ) THEN
225     cfFacMom = 1. _d 0
226     ELSE
227     cfFacMom = 0. _d 0
228     ENDIF
229     IF ( momPressureForcing ) THEN
230     pfFacMom = 1. _d 0
231     ELSE
232     pfFacMom = 0. _d 0
233     ENDIF
234 cnh 1.14 IF ( metricTerms ) THEN
235     mTFacMom = 1. _d 0
236     ELSE
237     mTFacMom = 1. _d 0
238     ENDIF
239 cnh 1.8
240     IF ( implicitFreeSurface .AND. rigidLid ) THEN
241     WRITE(msgBuf,'(A)')
242     & 'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'
243     CALL PRINT_ERROR( msgBuf , myThid)
244     STOP 'ABNORMAL END: S/R INI_PARMS'
245     ENDIF
246 cnh 1.1
247     C-- Elliptic solver parameters
248     cg2dMaxIters = 150
249     cg2dTargetResidual = 1. _d -7
250     cg2dChkResFreq = 1
251 cnh 1.7 cg2dpcOffDFac = 0.51 _d 0
252 cnh 1.1 READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
253     IF ( errIO .GE. 0 ) GOTO 6
254     5 CONTINUE
255     WRITE(msgBuf,'(A)')
256     & 'S/R INI_PARMS'
257     CALL PRINT_ERROR( msgBuf , 1)
258     WRITE(msgBuf,'(A)')
259     & 'Error reading numerical model '
260     CALL PRINT_ERROR( msgBuf , 1)
261     WRITE(msgBuf,'(A)')
262     & 'parameter file "data".'
263     CALL PRINT_ERROR( msgBuf , 1)
264     WRITE(msgBuf,'(A)')
265     & 'Problem in namelist PARM02'
266     CALL PRINT_ERROR( msgBuf , 1)
267     CALL MODELDATA_EXAMPLE( myThid )
268     STOP 'ABNORMAL END: S/R INI_PARMS'
269     6 CONTINUE
270    
271     C-- Time stepping parameters
272     startTime = 0.
273 cnh 1.4 nTimeSteps = 0
274     endTime = 0.
275 cnh 1.1 nIter0 = 0
276 cnh 1.4 deltaT = 0.
277 cnh 1.7 deltaTClock = 0.
278 cnh 1.4 deltaTtracer = 0.
279     deltaTMom = 0.
280 cnh 1.1 abEps = 0.01
281 cnh 1.7 pchkPtFreq = 0.
282 cnh 1.1 chkPtFreq = 3600.*25
283     dumpFreq = 3600.*100
284 cnh 1.7 writeStatePrec = precFloat32
285     nCheckLev = 1
286     checkPtSuff(1) = 'ckptA'
287     checkPtSuff(2) = 'ckptB'
288 cnh 1.9 cAdjFreq = -1. _d 0
289 cnh 1.14 rCD = -1. _d 0
290     tauCD = 0. _d 0
291 cnh 1.18 tauThetaClimRelax = 0. _d 0
292     doThetaClimRelax = .FALSE.
293     tauSaltClimRelax = 0. _d 0
294     doSaltClimRelax = .FALSE.
295 cnh 1.1 READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
296     IF ( errIO .GE. 0 ) GOTO 8
297     7 CONTINUE
298     WRITE(msgBuf,'(A)')
299     & 'S/R INI_PARMS'
300     CALL PRINT_ERROR( msgBuf , 1)
301     WRITE(msgBuf,'(A)')
302     & 'Error reading numerical model '
303     CALL PRINT_ERROR( msgBuf , 1)
304     WRITE(msgBuf,'(A)')
305     & 'parameter file "data"'
306     CALL PRINT_ERROR( msgBuf , 1)
307     WRITE(msgBuf,'(A)')
308     & 'Problem in namelist PARM03'
309     CALL PRINT_ERROR( msgBuf , 1)
310     CALL MODELDATA_EXAMPLE( myThid )
311     STOP 'ABNORMAL END: S/R INI_PARMS'
312     8 CONTINUE
313 cnh 1.4 C Process "timestepping" params
314     C o Time step size
315     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
316     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
317     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
318     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
319 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
320 cnh 1.9 C o Convection frequency
321     IF ( cAdjFreq .LT. 0. ) THEN
322     cAdjFreq = deltaTClock
323     ENDIF
324 cnh 1.14 C o CD coupling
325     IF ( tauCD .EQ. 0. _d 0 ) THEN
326     tauCD = deltaTmom
327     ENDIF
328     IF ( rCD .LT. 0. ) THEN
329     rCD = 1. - deltaTMom/tauCD
330     ENDIF
331 cnh 1.18 C o Temperature climatology relaxation time scale
332     IF ( tauThetaClimRelax .EQ. 0. _d 0 ) THEN
333     doThetaClimRelax = .FALSE.
334     lambdaThetaClimRelax = 0. _d 0
335     ELSE
336     doThetaClimRelax = .TRUE.
337     lambdaThetaClimRelax = 1./tauThetaClimRelax
338     ENDIF
339     C o Salinity climatology relaxation time scale
340     IF ( tauSaltClimRelax .EQ. 0. _d 0 ) THEN
341     doSaltClimRelax = .FALSE.
342     lambdaSaltClimRelax = 0. _d 0
343     ELSE
344     doSaltClimRelax = .TRUE.
345     lambdaSaltClimRelax = 1./tauSaltClimRelax
346     ENDIF
347 cnh 1.4 C o Time step count
348     IF ( endTime .NE. 0 ) THEN
349 cnh 1.7 IF ( deltaTClock .NE. 0 ) nTimeSteps =
350     & INT((endTime-startTime)/deltaTClock)
351 cnh 1.4 ENDIF
352     C o Finish time
353 cnh 1.7 IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
354 cnh 1.1
355     C-- Grid parameters
356     C In cartesian coords distances are in metres
357     usingCartesianGrid = .TRUE.
358     DO K =1,Nz
359     delZ(K) = 100. _d 0
360     ENDDO
361     dxSpacing = 20. _d 0 * 1000. _d 0
362     dySpacing = 20. _d 0 * 1000. _d 0
363     DO i=1,Nx
364     delX(i) = dxSpacing
365     ENDDO
366     DO j=1,Ny
367     delY(j) = dySpacing
368     ENDDO
369     C In spherical polar distances are in degrees
370     usingSphericalPolarGrid = .FALSE.
371 cnh 1.14 phiMin = -5.0
372     thetaMin = 0.
373     rSphere = 6370. * 1. _d 3
374     rRsphere = 1. _d 0/rSphere
375 cnh 1.1 IF ( usingSphericalPolarGrid ) THEN
376     dxSpacing = 1.
377     dySpacing = 1.
378     DO I=1,Nx
379     delX(I) = dxSpacing
380     ENDDO
381     DO J=1,Ny
382     delY(J) = dySpacing
383     ENDDO
384     ENDIF
385    
386     READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)
387     IF ( errIO .GE. 0 ) GOTO 10
388     9 CONTINUE
389     WRITE(msgBuf,'(A)')
390     & 'S/R INI_PARMS'
391     CALL PRINT_ERROR( msgBuf , 1)
392     WRITE(msgBuf,'(A)')
393     & 'Error reading numerical model '
394     CALL PRINT_ERROR( msgBuf , 1)
395     WRITE(msgBuf,'(A)')
396     & 'parameter file "data"'
397     CALL PRINT_ERROR( msgBuf , 1)
398     WRITE(msgBuf,'(A)')
399     & 'Problem in namelist PARM04'
400     CALL PRINT_ERROR( msgBuf , 1)
401     CALL MODELDATA_EXAMPLE( myThid )
402     STOP 'ABNORMAL END: S/R INI_PARMS'
403     10 CONTINUE
404 adcroft 1.11
405 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
406     rRSphere = 1. _d 0/rSphere
407     ELSE
408     rRSphere = 0.
409     ENDIF
410    
411 adcroft 1.11 C Initialize EOS coefficients (3rd order polynomial)
412     IF (eostype.eq.'POLY3') THEN
413     OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
414     READ(37,*) I
415     IF (I.NE.Nz) THEN
416     WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
417     WRITE(0,*) ' because bad # of levels in data'
418     STOP 'Bad data in POLY3.COEFFS'
419     ENDIF
420     READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)
421     DO K=1,Nz
422     READ(37,*) (eosC(I,K),I=1,9)
423     write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
424     & (eosC(I,K),I=1,9)
425     ENDDO
426     CLOSE(37)
427     ENDIF
428 cnh 1.1
429     goptCount = 0
430     IF ( usingCartesianGrid ) goptCount = goptCount+1
431     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
432     IF ( goptCount .NE. 1 ) THEN
433     WRITE(msgBuf,'(A)')
434     & 'S/R INI_PARMS: More than one coordinate system requested'
435     CALL PRINT_ERROR( msgBuf , myThid)
436     STOP 'ABNORMAL END: S/R INI_PARMS'
437 cnh 1.14 ENDIF
438    
439     IF ( usingCartesianGrid ) THEN
440     usingSphericalPolarMterms = .FALSE.
441     metricTerms = .FALSE.
442     mTFacMom = 0
443 cnh 1.18 useBetaPlaneF = .TRUE.
444 cnh 1.14 ENDIF
445     IF ( usingSphericalPolarGrid ) THEN
446     useConstantF = .FALSE.
447     useBetaPlaneF = .FALSE.
448     useSphereF = .TRUE.
449     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
450     usingSphericalPolarMterms = .TRUE.
451     metricTerms = .TRUE.
452     mTFacMom = 1
453 cnh 1.1 ENDIF
454 cnh 1.15
455     C-- Input files
456     bathyFile = ' '
457     hydrogSaltFile = ' '
458     hydrogThetaFile = ' '
459     zonalWindFile = ' '
460     meridWindFile = ' '
461 cnh 1.18 thetaClimFile = ' '
462 cnh 1.15 READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)
463     IF ( errIO .GE. 0 ) GOTO 12
464     11 CONTINUE
465     WRITE(msgBuf,'(A)')
466     & 'S/R INI_PARMS'
467     CALL PRINT_ERROR( msgBuf , 1)
468     WRITE(msgBuf,'(A)')
469     & 'Error reading numerical model '
470     CALL PRINT_ERROR( msgBuf , 1)
471     WRITE(msgBuf,'(A)')
472     & 'parameter file "data"'
473     CALL PRINT_ERROR( msgBuf , 1)
474     WRITE(msgBuf,'(A)')
475     & 'Problem in namelist PARM05'
476     CALL PRINT_ERROR( msgBuf , 1)
477     CALL MODELDATA_EXAMPLE( myThid )
478     STOP 'ABNORMAL END: S/R INI_PARMS'
479     12 CONTINUE
480 cnh 1.1
481     _END_MASTER(myThid)
482    
483     C-- Everyone else must wait for the parameters to be loaded
484     _BARRIER
485     C
486    
487     RETURN
488     END
489    

  ViewVC Help
Powered by ViewVC 1.1.22