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

Contents of /MITgcm/model/src/ini_eos.F

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


Revision 1.13 - (show annotations) (download)
Fri Nov 4 01:19:24 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.12: +3 -5 lines
remove unused variables (reduces number of compiler warning)

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_eos.F,v 1.12 2005/01/19 01:18:55 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5 #define EXCLUDE_EOS_CHECK
6
7 CBOP
8 C !ROUTINE: INI_EOS
9 C !INTERFACE:
10 subroutine ini_eos( myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE INI_EOS
14 C | o Initialise coefficients of equation of state.
15 C *==========================================================*
16 C \ev
17
18 C !USES:
19
20 implicit none
21 C == Global variables ==
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "EOS.h"
26 #include "GRID.h"
27 #include "DYNVARS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C == Routine arguments ==
31 C myThid - Number of this instance of INI_CORI
32 INTEGER myThid
33
34 C !LOCAL VARIABLES:
35 C == Local variables ==
36 C I,K - Loop counters
37 INTEGER I, K
38 CHARACTER*(MAX_LEN_MBUF) msgBuf
39
40 IF ( .NOT.fluidIsWater ) RETURN
41
42 equationOfState = eosType
43
44 do k = 1,6
45 eosJMDCFw(k) = 0. _d 0
46 end do
47 do k = 1,9
48 eosJMDCSw(k) = 0. _d 0
49 end do
50 do k = 1,5
51 eosJMDCKFw(k) = 0. _d 0
52 end do
53 do k = 1,7
54 eosJMDCKSw(k) = 0. _d 0
55 end do
56 do k = 1,14
57 eosJMDCKP(k) = 0. _d 0
58 end do
59 do k = 0,11
60 eosMDJWFnum(k) = 0. _d 0
61 end do
62 do k = 0,12
63 eosMDJWFden(k) = 0. _d 0
64 end do
65
66 if ( equationOfState .eq. 'LINEAR' ) then
67 if ( tAlpha .eq. UNSET_RL ) tAlpha = 2. _d -4
68 if ( sBeta .eq. UNSET_RL ) sBeta = 7.4 _d -4
69 elseif ( equationOfState .eq. 'POLY3' ) then
70 OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
71 READ(37,*) I
72 IF (I.NE.Nr) THEN
73 WRITE(msgBuf,'(A)')
74 & 'ini_eos: attempt to read POLY3.COEFFS failed'
75 CALL PRINT_ERROR( msgBuf , 1)
76 WRITE(msgBuf,'(A)')
77 & ' because bad # of levels in data'
78 CALL PRINT_ERROR( msgBuf , 1)
79 STOP 'Bad data in POLY3.COEFFS'
80 ENDIF
81 READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nr)
82 DO K=1,Nr
83 READ(37,*) (eosC(I,K),I=1,9)
84 ENDDO
85 CLOSE(37)
86
87 elseif ( equationOfState(1:5) .eq. 'JMD95'
88 & .or. equationOfState .eq. 'UNESCO' ) then
89 C
90 C Jackett & McDougall (1995, JPO) equation of state
91 C rho = R(salinity, potential temperature, pressure)
92 C pressure needs to be available (from the previous
93 C time step to linearize the problem)
94 C
95 if ( equationOfState .eq. 'JMD95Z' .and. usingPCoords ) then
96 write(msgBuf,'(A)')
97 & 'ini_eos: equation of state ''JMD95Z'' should not'
98 CALL PRINT_ERROR( msgBuf , 1)
99 write(msgBuf,'(A)')
100 & ' be used together with pressure coordinates.'
101 CALL PRINT_ERROR( msgBuf , 1)
102 write(msgBuf,'(A)')
103 & ' Use only ''JMD95P'' with ''OCEANICP''.'
104 CALL PRINT_ERROR( msgBuf , 1)
105 STOP 'ABNORMAL END: S/R INI_EOS'
106 endif
107
108 C coefficients nonlinear equation of state in pressure coordinates for
109 C 1. density of fresh water at p = 0
110 eosJMDCFw(1) = 999.842594 _d +00
111 eosJMDCFw(2) = 6.793952 _d -02
112 eosJMDCFw(3) = - 9.095290 _d -03
113 eosJMDCFw(4) = 1.001685 _d -04
114 eosJMDCFw(5) = - 1.120083 _d -06
115 eosJMDCFw(6) = 6.536332 _d -09
116 C 2. density of sea water at p = 0
117 eosJMDCSw(1) = 8.24493 _d -01
118 eosJMDCSw(2) = - 4.0899 _d -03
119 eosJMDCSw(3) = 7.6438 _d -05
120 eosJMDCSw(4) = - 8.2467 _d -07
121 eosJMDCSw(5) = 5.3875 _d -09
122 eosJMDCSw(6) = - 5.72466 _d -03
123 eosJMDCSw(7) = 1.0227 _d -04
124 eosJMDCSw(8) = - 1.6546 _d -06
125 eosJMDCSw(9) = 4.8314 _d -04
126 if ( equationOfState(1:5) .eq. 'JMD95' ) then
127 C 3. secant bulk modulus K of fresh water at p = 0
128 eosJMDCKFw(1) = 1.965933 _d +04
129 eosJMDCKFw(2) = 1.444304 _d +02
130 eosJMDCKFw(3) = - 1.706103 _d +00
131 eosJMDCKFw(4) = 9.648704 _d -03
132 eosJMDCKFw(5) = - 4.190253 _d -05
133 C 4. secant bulk modulus K of sea water at p = 0
134 eosJMDCKSw(1) = 5.284855 _d +01
135 eosJMDCKSw(2) = - 3.101089 _d -01
136 eosJMDCKSw(3) = 6.283263 _d -03
137 eosJMDCKSw(4) = - 5.084188 _d -05
138 eosJMDCKSw(5) = 3.886640 _d -01
139 eosJMDCKSw(6) = 9.085835 _d -03
140 eosJMDCKSw(7) = - 4.619924 _d -04
141 C 5. secant bulk modulus K of sea water at p
142 eosJMDCKP( 1) = 3.186519 _d +00
143 eosJMDCKP( 2) = 2.212276 _d -02
144 eosJMDCKP( 3) = - 2.984642 _d -04
145 eosJMDCKP( 4) = 1.956415 _d -06
146 eosJMDCKP( 5) = 6.704388 _d -03
147 eosJMDCKP( 6) = - 1.847318 _d -04
148 eosJMDCKP( 7) = 2.059331 _d -07
149 eosJMDCKP( 8) = 1.480266 _d -04
150 eosJMDCKP( 9) = 2.102898 _d -04
151 eosJMDCKP(10) = - 1.202016 _d -05
152 eosJMDCKP(11) = 1.394680 _d -07
153 eosJMDCKP(12) = - 2.040237 _d -06
154 eosJMDCKP(13) = 6.128773 _d -08
155 eosJMDCKP(14) = 6.207323 _d -10
156
157 elseif ( equationOfState .eq. 'UNESCO' ) then
158
159 write(msgBuf,'(a)')
160 & 'WARNING WARNING WARNING WARNING WARNING WARNING '
161 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
162 & SQUEEZE_RIGHT , 1)
163 write(msgBuf,'(a,a)')
164 & 'WARNING: using the UNESCO formula with potential ',
165 & 'temperature'
166 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
167 & SQUEEZE_RIGHT , 1)
168 write(msgBuf,'(a)')
169 & 'WARNING: can result in density errors of up to 5%'
170 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
171 & SQUEEZE_RIGHT , 1)
172 write(msgBuf,'(a)')
173 & 'WARNING: (see Jackett and McDougall 1995, JAOT)'
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT , 1)
176 write(msgBuf,'(a)')
177 & 'WARNING WARNING WARNING WARNING WARNING WARNING '
178 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
179 & SQUEEZE_RIGHT , 1)
180
181 C 3. secant bulk modulus K of fresh water at p = 0
182 eosJMDCKFw(1) = 1.965221 _d +04
183 eosJMDCKFw(2) = 1.484206 _d +02
184 eosJMDCKFw(3) = - 2.327105 _d +00
185 eosJMDCKFw(4) = 1.360477 _d -02
186 eosJMDCKFw(5) = - 5.155288 _d -05
187 C 4. secant bulk modulus K of sea water at p = 0
188 eosJMDCKSw(1) = 5.46746 _d +01
189 eosJMDCKSw(2) = - 0.603459 _d +00
190 eosJMDCKSw(3) = 1.09987 _d -02
191 eosJMDCKSw(4) = - 6.1670 _d -05
192 eosJMDCKSw(5) = 7.944 _d -02
193 eosJMDCKSw(6) = 1.6483 _d -02
194 eosJMDCKSw(7) = - 5.3009 _d -04
195 C 5. secant bulk modulus K of sea water at p
196 eosJMDCKP( 1) = 3.239908 _d +00
197 eosJMDCKP( 2) = 1.43713 _d -03
198 eosJMDCKP( 3) = 1.16092 _d -04
199 eosJMDCKP( 4) = - 5.77905 _d -07
200 eosJMDCKP( 5) = 2.2838 _d -03
201 eosJMDCKP( 6) = - 1.0981 _d -05
202 eosJMDCKP( 7) = - 1.6078 _d -06
203 eosJMDCKP( 8) = 1.91075 _d -04
204 eosJMDCKP( 9) = 8.50935 _d -05
205 eosJMDCKP(10) = - 6.12293 _d -06
206 eosJMDCKP(11) = 5.2787 _d -08
207 eosJMDCKP(12) = - 9.9348 _d -07
208 eosJMDCKP(13) = 2.0816 _d -08
209 eosJMDCKP(14) = 9.1697 _d -10
210 else
211 STOP 'INI_EOS: We should never reach this point!'
212 endif
213
214 elseif ( equationOfState .eq. 'MDJWF' ) then
215
216 eosMDJWFnum( 0) = 9.99843699 _d +02
217 eosMDJWFnum( 1) = 7.35212840 _d +00
218 eosMDJWFnum( 2) = -5.45928211 _d -02
219 eosMDJWFnum( 3) = 3.98476704 _d -04
220 eosMDJWFnum( 4) = 2.96938239 _d +00
221 eosMDJWFnum( 5) = -7.23268813 _d -03
222 eosMDJWFnum( 6) = 2.12382341 _d -03
223 eosMDJWFnum( 7) = 1.04004591 _d -02
224 eosMDJWFnum( 8) = 1.03970529 _d -07
225 eosMDJWFnum( 9) = 5.18761880 _d -06
226 eosMDJWFnum(10) = -3.24041825 _d -08
227 eosMDJWFnum(11) = -1.23869360 _d -11
228
229
230 eosMDJWFden( 0) = 1.00000000 _d +00
231 eosMDJWFden( 1) = 7.28606739 _d -03
232 eosMDJWFden( 2) = -4.60835542 _d -05
233 eosMDJWFden( 3) = 3.68390573 _d -07
234 eosMDJWFden( 4) = 1.80809186 _d -10
235 eosMDJWFden( 5) = 2.14691708 _d -03
236 eosMDJWFden( 6) = -9.27062484 _d -06
237 eosMDJWFden( 7) = -1.78343643 _d -10
238 eosMDJWFden( 8) = 4.76534122 _d -06
239 eosMDJWFden( 9) = 1.63410736 _d -09
240 eosMDJWFden(10) = 5.30848875 _d -06
241 eosMDJWFden(11) = -3.03175128 _d -16
242 eosMDJWFden(12) = -1.27934137 _d -17
243
244 elseif( equationOfState .eq. 'IDEALG' ) then
245 C
246 else
247
248 write(msgbuf,'(3a)') ' INI_EOS: equationOfState = "',
249 & equationOfState,'"'
250 call print_error( msgbuf, mythid )
251 stop 'ABNORMAL END: S/R INI_EOS'
252
253 end if
254
255 _BEGIN_MASTER( myThid )
256 C-- Check EOS initialisation:
257
258 call check_eos( myThid )
259
260 _END_MASTER( myThid )
261
262 RETURN
263 END
264
265 CBOP
266 C !ROUTINE: CHECK_EOS
267 C !INTERFACE:
268 subroutine check_eos( myThid )
269 C !DESCRIPTION: \bv
270 C *==========================================================*
271 C | SUBROUTINE CHECK_EOS
272 C | o check the equation of state.
273 C *==========================================================*
274 C \ev
275
276 C !USES:
277
278 implicit none
279 #include "SIZE.h"
280 #include "EEPARAMS.h"
281 #include "PARAMS.h"
282 #include "EOS.h"
283
284 C !INPUT/OUTPUT PARAMETERS:
285 C == Routine arguments ==
286 C myThid - Number of this instance of CHECK_EOS
287 INTEGER myThid
288
289 #ifndef EXCLUDE_EOS_CHECK
290 C !LOCAL VARIABLES:
291 C == Local variables ==
292 C bi,bj - Loop counters
293 C I,J,K
294 INTEGER bi, bj
295 INTEGER imin, imax, jmin, jmax
296 INTEGER I, J, K
297 _RL tFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
298 _RL sFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
299 _RL rhoLoc (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
300 _RL bulkMod(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
301 _RL psave
302
303 INTEGER ncheck, kcheck
304 PARAMETER ( ncheck = 13 )
305 _RL tloc(ncheck), ptloc(ncheck), sloc(ncheck), ploc(ncheck)
306 _RL rloc(ncheck), bloc(ncheck)
307
308 CHARACTER*(MAX_LEN_MBUF) msgBuf
309
310 DATA tloc
311 & /3.25905152915860 _d 0, 20.38687090048638 _d 0,
312 & 25.44820830309568 _d 0, 20.17368557065936 _d 0,
313 & 13.43397459640398 _d 0,
314 & 5. _d 0, 25. _d 0,
315 & 5. _d 0, 25. _d 0,
316 & 5. _d 0, 25. _d 0,
317 & 5. _d 0, 25. _d 0/,
318 & ptloc
319 & /3. _d 0, 20. _d 0,
320 & 25. _d 0, 20. _d 0,
321 & 12. _d 0,
322 & 5. _d 0, 25. _d 0,
323 & 5. _d 0, 25. _d 0,
324 & 4.03692566635316 _d 0, 22.84661726775120 _d 0,
325 & 3.62720389416752 _d 0, 22.62420229124846 _d 0/
326 & sloc
327 & /35.5 _d 0, 35. _d 0,
328 & 35.0 _d 0, 20. _d 0,
329 & 40.0 _d 0,
330 & 0. _d 0, 0. _d 0,
331 & 35. _d 0, 35. _d 0,
332 & 0. _d 0, 0. _d 0,
333 & 35. _d 0, 35. _d 0/
334 & ploc
335 & /300. _d 5, 200. _d 5,
336 & 200. _d 5, 100. _d 5,
337 & 800. _d 5,
338 & 0. _d 0, 0. _d 0,
339 & 0. _d 0, 0. _d 0,
340 & 1000. _d 5, 1000. _d 5,
341 & 1000. _d 5, 1000. _d 5/
342 DATA rloc
343 & /1041.83267 _d 0, 1033.213387 _d 0,
344 & 1031.654229 _d 0, 1017.726743 _d 0,
345 & 1062.928258 _d 0,
346 & 999.96675 _d 0, 997.04796 _d 0,
347 & 1027.67547 _d 0, 1023.34306 _d 0,
348 & 1044.12802 _d 0, 1037.90204 _d 0,
349 & 1069.48914 _d 0, 1062.53817 _d 0/
350 & bloc
351 & / -1.00000 _d 0, -1.00000 _d 0,
352 & -1.00000 _d 0, -1.00000 _d 0,
353 & -1.00000 _d 0,
354 & 20337.80375 _d 0, 22100.72106 _d 0,
355 & 22185.93358 _d 0, 23726.34949 _d 0,
356 & 23643.52599 _d 0, 25405.09717 _d 0,
357 & 25577.49819 _d 0, 27108.94504 _d 0/
358
359
360 bi = 1
361 bj = 1
362 k = 1
363 imin = 1
364 imax = 1
365 jmin = 1
366 jmax = 1
367 i = 1
368 j = 1
369 if ( equationOfState.ne.'LINEAR'
370 & .and. equationOfState.ne.'POLY3' ) then
371 C check nonlinear EOS
372 write(msgBuf,'(a,a)')
373 & 'check_eos: Check the equation of state: Type ',
374 & equationOfState
375 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
376 & SQUEEZE_RIGHT , 1)
377 psave = pressure(i,j,k,bi,bj)
378 do kcheck = 1,ncheck
379 pressure(i,j,k,bi,bj) = ploc(kcheck)
380 if ( equationOfState.ne.'UNESCO' ) then
381 tFld(i,j,k,bi,bj) = ptloc(kcheck)
382 else
383 tFld(i,j,k,bi,bj) = tloc(kcheck)
384 endif
385 sFld(i,j,k,bi,bj) = sloc(kcheck)
386 rholoc(i,j) = 0. _d 0
387 bulkMod(i,j) = -1. _d 0
388
389 call find_rho(
390 & bi, bj, iMin, iMax, jMin, jMax, k, k,
391 & tFld, sFld, rholoc, myThid )
392
393 call find_bulkmod(
394 & bi, bj, imin, imax, jmin, jmax, k, k,
395 & tFld, sFld, bulkMod, myThid )
396
397 write(msgBuf,
398 & '(a4,f4.1,a5,f4.1,a6,f5.0,a5,a3,f10.5,1x,f11.5)')
399 & 'rho(', sFld(i,j,k,bi,bj), ' PSU,',
400 & tFld(i,j,k,bi,bj), ' degC,',
401 c & pressure(i,j,k,bi,bj)*SItoBar, ' bar)',' = ',
402 & rloc(kcheck), bloc(kcheck)
403 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
404 & SQUEEZE_RIGHT , 1)
405 write(msgBuf,'(a14,a22,f10.5,1x,f11.5)')
406 & 'rho(find_rho) ',
407 & ' = ', rholoc(i,j)+rhoConst, bulkMod(i,j)
408 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
409 & SQUEEZE_RIGHT , 1)
410
411 call find_rho_scalar( tFld(i,j,k,bi,bj), sLoc(kcheck),
412 & pLoc(kcheck), rhoLoc(i,j), myThid )
413 bulkMod(i,j) = 0. _d 0
414 write(msgBuf,'(a21,a15,f10.5,1x,f11.5)')
415 & 'rho(find_rho_scalar) ',
416 & ' = ', rholoc(i,j)+rhoConst, bulkMod(i,j)
417 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
418 & SQUEEZE_RIGHT , 1)
419
420 enddo
421 C end check nonlinear EOS
422 c pressure(i,j,k,bi,bj) = psave
423
424 write(msgBuf,'(A)') 'end check the equation of state'
425 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
426 & SQUEEZE_RIGHT , 1)
427
428 endif
429 #endif /* EXCLUDE_EOS_CHECK */
430
431 RETURN
432 END
433

  ViewVC Help
Powered by ViewVC 1.1.22