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 @ 336

Last change on this file since 336 was 333, checked in by opalod, 19 years ago

nemo_v1_update_021 : CE + RB + CT : add the CFC main routine and p4z new routines

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