/[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.15 - (hide annotations) (download)
Tue Jun 9 16:48:02 1998 UTC (26 years ago) by cnh
Branch: MAIN
Changes since 1.14: +31 -1 lines
Changes to support topography, hydrography and
forcing from files

1 cnh 1.15 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_parms.F,v 1.14 1998/06/08 21:43:01 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.12 & tempStepping, 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     & cAdjFreq
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     & zonalWindFile, meridWindFile
87    
88 cnh 1.1 C
89     _BEGIN_MASTER(myThid)
90    
91     C-- Open the parameter file
92     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
93     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
94     OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',err=1,IOSTAT=errIO)
95     IF ( errIO .GE. 0 ) GOTO 2
96     1 CONTINUE
97     WRITE(msgBuf,'(A)')
98     & 'S/R INI_PARMS'
99     CALL PRINT_ERROR( msgBuf , 1)
100     WRITE(msgBuf,'(A)')
101     & 'Unable to open model parameter'
102     CALL PRINT_ERROR( msgBuf , 1)
103     WRITE(msgBuf,'(A)')
104     & 'file "data"'
105     CALL PRINT_ERROR( msgBuf , 1)
106     CALL MODELDATA_EXAMPLE( myThid )
107     STOP 'ABNORMAL END: S/R INI_PARMS'
108     2 CONTINUE
109    
110     1000 CONTINUE
111     READ(modelDataUnit,FMT='(A)',END=1001) RECORD
112     IL = MAX(ILNBLNK(RECORD),1)
113     IF ( RECORD(1:1) .NE. commentCharacter )
114     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
115     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
116     GOTO 1000
117     1001 CONTINUE
118     CLOSE(modelDataUnit)
119    
120     C-- Report contents of model parameter file
121     WRITE(msgBuf,'(A)')
122     &'// ======================================================='
123     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
124     WRITE(msgBuf,'(A)') '// Model parameter file "data"'
125     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
126     WRITE(msgBuf,'(A)')
127     &'// ======================================================='
128     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
129     & SQUEEZE_RIGHT , 1)
130     iUnit = scrUnit2
131     REWIND(iUnit)
132     2000 CONTINUE
133     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
134     IL = MAX(ILNBLNK(RECORD),1)
135     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
136     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
137     GOTO 2000
138     2001 CONTINUE
139     CLOSE(iUnit)
140     WRITE(msgBuf,'(A)') ' '
141     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
142     & SQUEEZE_RIGHT , 1)
143    
144    
145     C-- Read settings from model parameter file "data".
146     iUnit = scrUnit1
147     REWIND(iUnit)
148    
149     C-- Set default "physical" parameters
150     DO K =1,Nz
151     tRef(K) = 30.D0 - FLOAT(K)
152     ENDDO
153     gravity = 9.81 D0
154 cnh 1.8 gBaro = gravity
155 cnh 1.1 rhoNil = 999.8 D0
156     f0=1.D-4
157     beta = 1. _d -11
158     viscAh=1.d3
159     viscA4=0.
160     viscAz=1.d-3
161     diffKhT=1.0d3
162     diffKzT=1.d-5
163     diffKhS=1.0d3
164     diffKzS=1.d-1
165     diffK4T=0.
166     diffK4S=0.
167 adcroft 1.6 GMmaxslope=1.d-2
168     GMlength=200.d3
169     GMalpha=0.
170     GMdepth=1000.
171     GMkbackground=0.
172 adcroft 1.11 tAlpha=2.d-4
173     sBeta=1.d-5
174 adcroft 1.13 eosType='LINEAR'
175 cnh 1.8 implicitFreeSurface = .TRUE.
176     rigidLid = .FALSE.
177     freeSurfFac = 1. _d 0
178 cnh 1.9 momViscosity = .TRUE.
179     momAdvection = .TRUE.
180     momForcing = .TRUE.
181     useCoriolis = .TRUE.
182     momPressureForcing = .TRUE.
183 cnh 1.10 momStepping = .TRUE.
184     tempStepping = .TRUE.
185 cnh 1.14 metricTerms = .TRUE.
186 adcroft 1.12 implicitDiffusion = .FALSE.
187 cnh 1.1 READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)
188     IF ( errIO .GE. 0 ) GOTO 4
189     3 CONTINUE
190     WRITE(msgBuf,'(A)')
191     & 'S/R INI_PARMS'
192     CALL PRINT_ERROR( msgBuf , 1)
193     WRITE(msgBuf,'(A)')
194     & 'Error reading numerical model '
195     CALL PRINT_ERROR( msgBuf , 1)
196     WRITE(msgBuf,'(A)')
197     & 'parameter file "data"'
198     CALL PRINT_ERROR( msgBuf , 1)
199     WRITE(msgBuf,'(A)')
200     & 'Problem in namelist PARM01'
201     CALL PRINT_ERROR( msgBuf , 1)
202     CALL MODELDATA_EXAMPLE( myThid )
203     STOP 'ABNORMAL END: S/R INI_PARMS'
204     4 CONTINUE
205 cnh 1.8 IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0
206     IF ( rigidLid ) freeSurfFac = 0. _d 0
207 cnh 1.9 IF ( momViscosity ) THEN
208     vfFacMom = 1. _d 0
209     ELSE
210     vfFacMom = 0. _d 0
211     ENDIF
212     IF ( momAdvection ) THEN
213     afFacMom = 1. _d 0
214     ELSE
215     afFacMom = 0. _d 0
216     ENDIF
217     IF ( momForcing ) THEN
218     foFacMom = 1. _d 0
219     ELSE
220     foFacMom = 0. _d 0
221     ENDIF
222     IF ( useCoriolis ) THEN
223     cfFacMom = 1. _d 0
224     ELSE
225     cfFacMom = 0. _d 0
226     ENDIF
227     IF ( momPressureForcing ) THEN
228     pfFacMom = 1. _d 0
229     ELSE
230     pfFacMom = 0. _d 0
231     ENDIF
232 cnh 1.14 IF ( metricTerms ) THEN
233     mTFacMom = 1. _d 0
234     ELSE
235     mTFacMom = 1. _d 0
236     ENDIF
237 cnh 1.8
238     IF ( implicitFreeSurface .AND. rigidLid ) THEN
239     WRITE(msgBuf,'(A)')
240     & 'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'
241     CALL PRINT_ERROR( msgBuf , myThid)
242     STOP 'ABNORMAL END: S/R INI_PARMS'
243     ENDIF
244 cnh 1.1
245     C-- Elliptic solver parameters
246     cg2dMaxIters = 150
247     cg2dTargetResidual = 1. _d -7
248     cg2dChkResFreq = 1
249 cnh 1.7 cg2dpcOffDFac = 0.51 _d 0
250 cnh 1.1 READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
251     IF ( errIO .GE. 0 ) GOTO 6
252     5 CONTINUE
253     WRITE(msgBuf,'(A)')
254     & 'S/R INI_PARMS'
255     CALL PRINT_ERROR( msgBuf , 1)
256     WRITE(msgBuf,'(A)')
257     & 'Error reading numerical model '
258     CALL PRINT_ERROR( msgBuf , 1)
259     WRITE(msgBuf,'(A)')
260     & 'parameter file "data".'
261     CALL PRINT_ERROR( msgBuf , 1)
262     WRITE(msgBuf,'(A)')
263     & 'Problem in namelist PARM02'
264     CALL PRINT_ERROR( msgBuf , 1)
265     CALL MODELDATA_EXAMPLE( myThid )
266     STOP 'ABNORMAL END: S/R INI_PARMS'
267     6 CONTINUE
268    
269     C-- Time stepping parameters
270     startTime = 0.
271 cnh 1.4 nTimeSteps = 0
272     endTime = 0.
273 cnh 1.1 nIter0 = 0
274 cnh 1.4 deltaT = 0.
275 cnh 1.7 deltaTClock = 0.
276 cnh 1.4 deltaTtracer = 0.
277     deltaTMom = 0.
278 cnh 1.1 abEps = 0.01
279 cnh 1.7 pchkPtFreq = 0.
280 cnh 1.1 chkPtFreq = 3600.*25
281     dumpFreq = 3600.*100
282 cnh 1.7 writeStatePrec = precFloat32
283     nCheckLev = 1
284     checkPtSuff(1) = 'ckptA'
285     checkPtSuff(2) = 'ckptB'
286 cnh 1.9 cAdjFreq = -1. _d 0
287 cnh 1.14 rCD = -1. _d 0
288     tauCD = 0. _d 0
289 cnh 1.1 READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
290     IF ( errIO .GE. 0 ) GOTO 8
291     7 CONTINUE
292     WRITE(msgBuf,'(A)')
293     & 'S/R INI_PARMS'
294     CALL PRINT_ERROR( msgBuf , 1)
295     WRITE(msgBuf,'(A)')
296     & 'Error reading numerical model '
297     CALL PRINT_ERROR( msgBuf , 1)
298     WRITE(msgBuf,'(A)')
299     & 'parameter file "data"'
300     CALL PRINT_ERROR( msgBuf , 1)
301     WRITE(msgBuf,'(A)')
302     & 'Problem in namelist PARM03'
303     CALL PRINT_ERROR( msgBuf , 1)
304     CALL MODELDATA_EXAMPLE( myThid )
305     STOP 'ABNORMAL END: S/R INI_PARMS'
306     8 CONTINUE
307 cnh 1.4 C Process "timestepping" params
308     C o Time step size
309     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
310     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
311     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
312     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
313 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
314 cnh 1.9 C o Convection frequency
315     IF ( cAdjFreq .LT. 0. ) THEN
316     cAdjFreq = deltaTClock
317     ENDIF
318 cnh 1.14 C o CD coupling
319     IF ( tauCD .EQ. 0. _d 0 ) THEN
320     tauCD = deltaTmom
321     ENDIF
322     IF ( rCD .LT. 0. ) THEN
323     rCD = 1. - deltaTMom/tauCD
324     ENDIF
325 cnh 1.4 C o Time step count
326     IF ( endTime .NE. 0 ) THEN
327 cnh 1.7 IF ( deltaTClock .NE. 0 ) nTimeSteps =
328     & INT((endTime-startTime)/deltaTClock)
329 cnh 1.4 ENDIF
330     C o Finish time
331 cnh 1.7 IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
332 cnh 1.1
333     C-- Grid parameters
334     C In cartesian coords distances are in metres
335     usingCartesianGrid = .TRUE.
336     DO K =1,Nz
337     delZ(K) = 100. _d 0
338     ENDDO
339     dxSpacing = 20. _d 0 * 1000. _d 0
340     dySpacing = 20. _d 0 * 1000. _d 0
341     DO i=1,Nx
342     delX(i) = dxSpacing
343     ENDDO
344     DO j=1,Ny
345     delY(j) = dySpacing
346     ENDDO
347     C In spherical polar distances are in degrees
348     usingSphericalPolarGrid = .FALSE.
349 cnh 1.14 phiMin = -5.0
350     thetaMin = 0.
351     rSphere = 6370. * 1. _d 3
352     rRsphere = 1. _d 0/rSphere
353 cnh 1.1 IF ( usingSphericalPolarGrid ) THEN
354     dxSpacing = 1.
355     dySpacing = 1.
356     DO I=1,Nx
357     delX(I) = dxSpacing
358     ENDDO
359     DO J=1,Ny
360     delY(J) = dySpacing
361     ENDDO
362     ENDIF
363    
364     READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)
365     IF ( errIO .GE. 0 ) GOTO 10
366     9 CONTINUE
367     WRITE(msgBuf,'(A)')
368     & 'S/R INI_PARMS'
369     CALL PRINT_ERROR( msgBuf , 1)
370     WRITE(msgBuf,'(A)')
371     & 'Error reading numerical model '
372     CALL PRINT_ERROR( msgBuf , 1)
373     WRITE(msgBuf,'(A)')
374     & 'parameter file "data"'
375     CALL PRINT_ERROR( msgBuf , 1)
376     WRITE(msgBuf,'(A)')
377     & 'Problem in namelist PARM04'
378     CALL PRINT_ERROR( msgBuf , 1)
379     CALL MODELDATA_EXAMPLE( myThid )
380     STOP 'ABNORMAL END: S/R INI_PARMS'
381     10 CONTINUE
382 adcroft 1.11
383 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
384     rRSphere = 1. _d 0/rSphere
385     ELSE
386     rRSphere = 0.
387     ENDIF
388    
389 adcroft 1.11 C Initialize EOS coefficients (3rd order polynomial)
390     IF (eostype.eq.'POLY3') THEN
391     OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
392     READ(37,*) I
393     IF (I.NE.Nz) THEN
394     WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
395     WRITE(0,*) ' because bad # of levels in data'
396     STOP 'Bad data in POLY3.COEFFS'
397     ENDIF
398     READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)
399     DO K=1,Nz
400     READ(37,*) (eosC(I,K),I=1,9)
401     write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
402     & (eosC(I,K),I=1,9)
403     ENDDO
404     CLOSE(37)
405     ENDIF
406 cnh 1.1
407     goptCount = 0
408     IF ( usingCartesianGrid ) goptCount = goptCount+1
409     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
410     IF ( goptCount .NE. 1 ) THEN
411     WRITE(msgBuf,'(A)')
412     & 'S/R INI_PARMS: More than one coordinate system requested'
413     CALL PRINT_ERROR( msgBuf , myThid)
414     STOP 'ABNORMAL END: S/R INI_PARMS'
415 cnh 1.14 ENDIF
416    
417     IF ( usingCartesianGrid ) THEN
418     usingSphericalPolarMterms = .FALSE.
419     metricTerms = .FALSE.
420     mTFacMom = 0
421    
422     useConstantF = .FALSE.
423     useBetaPlaneF = .FALSE.
424     useSphereF = .TRUE.
425     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
426     usingSphericalPolarMterms = .TRUE.
427     metricTerms = .TRUE.
428     mTFacMom = 1
429     ENDIF
430     IF ( usingSphericalPolarGrid ) THEN
431     useConstantF = .FALSE.
432     useBetaPlaneF = .FALSE.
433     useSphereF = .TRUE.
434     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
435     usingSphericalPolarMterms = .TRUE.
436     metricTerms = .TRUE.
437     mTFacMom = 1
438 cnh 1.1 ENDIF
439 cnh 1.15
440     C-- Input files
441     bathyFile = ' '
442     hydrogSaltFile = ' '
443     hydrogThetaFile = ' '
444     zonalWindFile = ' '
445     meridWindFile = ' '
446     READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)
447     IF ( errIO .GE. 0 ) GOTO 12
448     11 CONTINUE
449     WRITE(msgBuf,'(A)')
450     & 'S/R INI_PARMS'
451     CALL PRINT_ERROR( msgBuf , 1)
452     WRITE(msgBuf,'(A)')
453     & 'Error reading numerical model '
454     CALL PRINT_ERROR( msgBuf , 1)
455     WRITE(msgBuf,'(A)')
456     & 'parameter file "data"'
457     CALL PRINT_ERROR( msgBuf , 1)
458     WRITE(msgBuf,'(A)')
459     & 'Problem in namelist PARM05'
460     CALL PRINT_ERROR( msgBuf , 1)
461     CALL MODELDATA_EXAMPLE( myThid )
462     STOP 'ABNORMAL END: S/R INI_PARMS'
463     12 CONTINUE
464 cnh 1.1
465     _END_MASTER(myThid)
466    
467     C-- Everyone else must wait for the parameters to be loaded
468     _BARRIER
469     C
470    
471     RETURN
472     END
473    

  ViewVC Help
Powered by ViewVC 1.1.22