/[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.9 - (hide annotations) (download)
Mon Feb 3 21:58:09 2003 UTC (21 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48e_post, checkpoint48d_pre, checkpoint48d_post, checkpoint48f_post
Changes since 1.8: +23 -5 lines
Wrong Restart when using Z-coord with EOS function of P. => add a warning

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

  ViewVC Help
Powered by ViewVC 1.1.22