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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 7 16:55:52 2002 UTC (21 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46b_post, checkpoint46d_pre, checkpoint46c_pre, checkpoint46c_post
o Added new equation of state -> JMD95Z and JMD95P
  - EOS of Jackett and McDougall, 1995, JPO
  - moved all EOS parameters into EOS.h
  - new routines ini_eos.F, store_pressure.F
o Added UNESCO EOS, but not recommended because it requires
  in-situ temperature (see JMD95)
o Modified formatting for knudsen2.f in utils/knudsen2 and added
  unesco.f to be used with POLY3

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

  ViewVC Help
Powered by ViewVC 1.1.22