New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcfreons.F90 in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/trcfreons.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.3 KB
Line 
1MODULE trcfreons
2   !!==============================================================
3   !!                  ***  MODULE trcfreons  ***
4   !!  Passive tracer : CFC main model
5   !!==============================================================
6#if defined key_cfc
7   !!--------------------------------------------------------------
8   !!   'key_cfc'                                         CFC model
9   !!--------------------------------------------------------------
10   !! * Modules used   
11   USE daymod
12   USE sms
13   USE oce_trc
14   USE trc
15
16
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Routine accessibility
21   PUBLIC trc_freons       
22
23   !! * Module variables
24   REAL(wp), DIMENSION(jptra) :: & ! coefficient for solubility of CFC11 in  mol/l/atm
25      soa1, soa2, soa3, soa4, &
26      sob1, sob2, sob3
27
28   REAL(wp), DIMENSION(jptra) :: & ! coefficients for schmidt number in degre Celcius
29      sca1, sca2, sca3, sca4
30
31   REAL(wp) ::              & ! coefficients for conversion
32      xconv1 = 1.0       ,  & ! conversion from to
33      xconv2 = 0.01/3600.,  & ! conversion from cm/h to m/s:
34      xconv3 = 1.0e+3    ,  & ! conversion from mol/l/atm to mol/m3/atm
35      xconv4 = 1.0e-12        ! conversion from mol/m3/atm to mol/m3/pptv
36
37   !! * Substitutions
38#  include "passivetrc_substitute.h90"
39
40   !!----------------------------------------------------------------------
41   !!  TOP 1.0 , LOCEAN-IPSL (2005)
42   !! $Header$
43   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE trc_freons( kt )
49      !!----------------------------------------------------------------------
50      !!                  ***  ROUTINE trc_freons  ***
51      !!
52      !! ** Purpose :   Compute the surface boundary contition on freon 11
53      !!      passive tracer associated with air-mer fluxes and add it to
54      !!      the general trend of tracers equations.
55      !!
56      !! ** Method :
57      !!          - get the atmospheric partial pressure - given in pico -
58      !!          - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3)
59      !!          - computation of transfert speed ( given in cm/hour ----> cm/s )
60      !!          - the input function is given by :
61      !!            speed * ( concentration at equilibrium - concemtration at surface )
62      !!          - the input function is in pico-mol/m3/s and the
63      !!            freons concentration in pico-mol/m3
64      !!
65      !! History :
66      !!   8.1  !  99-10  (JC. Dutay)  original code
67      !!   9.0  !  04-03  (C. Ethe)  free form + modularity
68      !!----------------------------------------------------------------------
69      !! * Arguments
70      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
71
72      !! * Local declarations
73      INTEGER ::  &
74         ji, jj, jn, jm
75
76      INTEGER ::   &
77         iyear_beg, iyear_end, &
78         imonth, im1, im2
79
80      REAL(wp) :: &
81         ztap, zdtap, &
82         zt1, zt2, zt3, zv2
83
84      REAL(wp), DIMENSION(jphem,jptra)   ::  &   
85         zpatm       ! atmospheric function
86
87      REAL(wp) ::  & 
88         zsol,     & ! solubility
89         zsch        ! schmidt number
90
91     
92      REAL(wp), DIMENSION(jpi,jpj,jptra)   ::  & 
93         zca_cfc,  & ! concentration
94         zak_cfc     ! transfert coefficients
95
96      !!----------------------------------------------------------------------
97
98
99      IF( kt == nittrc000 )   CALL trc_freons_cst
100
101      ! Temporal interpolation
102      ! ----------------------
103      iyear_beg = nyear + ( nyear_res - 1900 - nyear_beg  )
104      imonth    = nmonth
105
106      IF ( imonth .LE. 6 ) THEN
107         iyear_beg = iyear_beg - 2 + nyear_beg
108         im1       = 6 - imonth + 1
109         im2       = 6 + imonth - 1
110      ELSE
111         iyear_beg = iyear_beg - 1 + nyear_beg
112         im1       = 12 - imonth + 7
113         im2       =      imonth - 7
114      ENDIF
115
116      iyear_end = iyear_beg + 1
117
118
119
120
121      !  Temporal and spatial interpolation at time k
122      ! --------------------------------------------------
123      DO jn = 1, jptra
124         DO  jm = 1, jphem
125            zpatm(jm,jn) = (  p_cfc(iyear_beg, jm, jn) * FLOAT (im1)  &
126               &           +  p_cfc(iyear_end, jm, jn) * FLOAT (im2) ) / 12.
127         ENDDO
128      END DO
129
130      DO jn = 1, jptra
131         DO jj = 1, jpj 
132            DO ji = 1, jpi
133               pp_cfc(ji,jj,jn) =     xphem(ji,jj)   * zpatm(1,jn)  &
134                  &           + ( 1.- xphem(ji,jj) ) * zpatm(2,jn)
135            END DO
136         END DO
137      ENDDO
138
139
140      !------------------------------------------------------------
141      ! Computation of concentration at equilibrium : in picomol/l
142      ! -----------------------------------------------------------
143
144      DO jn = 1, jptra
145         DO jj = 1 , jpj
146            DO ji = 1 , jpi
147               ! coefficient for solubility for CFC-11/12 in  mol/l/atm
148               IF( tmask(ji,jj,1) .GE. 0.5 ) THEN
149                  ztap  = ( tn(ji,jj,1) + 273.16 )* 0.01
150                  zdtap = ( sob3(jn) * ztap + sob2(jn))* ztap + sob1(jn) 
151                  zsol  =  EXP ( soa1(jn) + soa2(jn) / ztap + soa3(jn) * LOG ( ztap )   &
152                     &                   + soa4(jn) * ztap * ztap + sn(ji,jj,1) * zdtap ) 
153               ELSE
154                  zsol  = 0.
155               ENDIF
156               ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv   
157               zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) 
158               ! concentration at equilibrium
159               zca_cfc(ji,jj,jn) = xconv1 * pp_cfc(ji,jj,jn) * zsol * tmask(ji,jj,1)             
160            END DO
161         END DO
162      ENDDO
163
164 
165      !-------------------------------
166      ! Computation of speed transfert
167      ! ------------------------------
168
169      DO jn = 1, jptra
170         DO jj = 1, jpj
171            DO ji = 1, jpi
172               ! Schmidt number
173               zt1  = tn(ji,jj,1)
174               zt2  = zt1 * zt1 
175               zt3  = zt1 * zt2
176               zsch = sca1(jn) + sca2(jn) * zt1 + sca3(jn) * zt2 + sca4(jn) * zt3
177               ! speed transfert : formulae of wanninkhof 1992
178               zv2 = vatm(ji,jj) * vatm(ji,jj)
179               zsch = zsch / 660.
180               zak_cfc(ji,jj,jn) = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1)
181            END DO
182         END DO
183      ENDDO
184
185
186      !----------------------------------------------------------------
187      ! Input function  : speed *( conc. at equil - concen at surface )
188      ! trn in pico-mol/l idem qtr; ak in en m/s
189      !-----------------------------------------------------------------
190
191      DO jn = 1, jptra
192         DO jj = 1, jpj
193            DO ji = 1, jpi
194               qtr(ji,jj,jn) = -zak_cfc(ji,jj,jn) * ( trb(ji,jj,1,jn) - zca_cfc(ji,jj,jn) )   &
195#if defined key_off_degrad
196                  &                               * facvol(ji,jj,1)                           &
197#endif
198                  &                               * tmask(ji,jj,1) * ( 1. - freeze(ji,jj) )
199            END DO
200         END DO
201      ENDDO
202
203
204      ! ---------------------
205      ! Add the trend
206      ! ---------------------
207
208      DO jn = 1, jptra
209         DO  jj = 1, jpj
210            DO  ji = 1, jpi
211               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr(ji,jj,jn) / fse3t(ji,jj,1) 
212            END DO
213         END DO
214      ENDDO
215
216      ! --------------------------------------------
217      ! cumulation of tracer flux at each time step
218      ! --------------------------------------------
219      DO jn = 1, jptra
220         DO jj = 1, jpj
221            DO ji = 1, jpi
222               qint(ji,jj,jn) = qint (ji,jj,jn) + qtr(ji,jj,jn) * rdt
223            END DO
224         END DO
225      ENDDO
226
227
228   END SUBROUTINE trc_freons
229
230   SUBROUTINE trc_freons_cst
231      !!---------------------------------------------------------------------
232      !!                     ***  trc_freons_cst  *** 
233      !!
234      !!   Purpose : sets constants for CFC model
235      !!  ---------
236      !!
237      !!
238      !! History :
239      !!   8.2  !  04-06  (JC. Dutay)  original code
240      !!   9.0  !  05-10  (C. Ethe) Modularity
241      !!---------------------------------------------------------------------
242      !!  TOP 1.0 , LOCEAN-IPSL (2005)
243   !! $Header$
244   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
245      !!----------------------------------------------------------------
246      !! Local declarations
247      INTEGER :: jn
248
249      DO jn = 1, jptra
250         IF ( jn == jp11 ) THEN
251            ! coefficient for solubility of CFC11 in  mol/l/atm
252            soa1(jn) = -229.9261 
253            soa2(jn) =  319.6552
254            soa3(jn) =  119.4471
255            soa4(jn) =  -1.39165
256            sob1(jn) =  -0.142382
257            sob2(jn) =   0.091459
258            sob3(jn) =  -0.0157274
259           
260            ! coefficients for schmidt number in degre Celcius
261            sca1(jn) = 3501.8
262            sca2(jn) = -210.31
263            sca3(jn) = 6.1851
264            sca4(jn) = -0.07513
265
266         ELSE IF( jn == jp12 ) THEN
267
268            ! coefficient for solubility of CFC12 in  mol/l/atm
269            soa1(jn) = -218.0971
270            soa2(jn) =  298.9702
271            soa3(jn) =  113.8049
272            soa4(jn) =  -1.39165
273            sob1(jn) =  -0.143566
274            sob2(jn) =   0.091015
275            sob3(jn) =  -0.0153924
276                       
277            ! coefficients for schmidt number in degre Celcius
278            sca1(jn) =  3845.4 
279            sca2(jn) = -228.95
280            sca3(jn) = 6.1908 
281            sca4(jn) = -0.067430
282         ENDIF
283      ENDDO
284
285      DO jn = 1, jptra
286         WRITE(numout,*) 'coefficient for solubility of tracer',ctrcnm(jn)
287         WRITE(numout,*) soa1(jn), soa2(jn),soa3(jn), soa4(jn), &
288            &           sob1(jn), sob2(jn),sob3(jn)
289         WRITE(numout,*) 
290         WRITE(numout,*) 'coefficient for schmidt of tracer',ctrcnm(jn)
291         WRITE(numout,*) sca1(jn), sca2(jn),sca3(jn), sca4(jn)
292      ENDDO
293
294   END SUBROUTINE trc_freons_cst
295#else
296   !!----------------------------------------------------------------------
297   !!   Default option                                         Dummy module
298   !!----------------------------------------------------------------------
299CONTAINS
300   SUBROUTINE trc_freons( kt )       ! Empty routine
301      WRITE(*,*) 'trc_freons: You should not have seen this print! error?', kt
302   END SUBROUTINE trc_freons
303#endif
304
305   !!======================================================================
306END MODULE trcfreons
Note: See TracBrowser for help on using the repository browser.