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.
trcsms_cfc.F90 in trunk/NEMO/TOP_SRC/CFC – NEMO

source: trunk/NEMO/TOP_SRC/CFC/trcsms_cfc.F90 @ 1255

Last change on this file since 1255 was 1255, checked in by cetlod, 15 years ago

minor modifications in all top models, see ticket:299

  • Property svn:keywords set to Id
File size: 10.7 KB
Line 
1MODULE trcsms_cfc
2   !!======================================================================
3   !!                      ***  MODULE trcsms_cfc  ***
4   !! TOP : CFC main model
5   !!======================================================================
6   !! History :    -   !  1999-10  (JC. Dutay)  original code
7   !!             1.0  !  2004-03 (C. Ethe) free form + modularity
8   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation
9   !!----------------------------------------------------------------------
10#if defined key_cfc
11   !!----------------------------------------------------------------------
12   !!   'key_cfc'                                               CFC tracers
13   !!----------------------------------------------------------------------
14   !!   trc_sms_cfc     :  compute and add CFC suface forcing to CFC trends
15   !!   trc_cfc_cst :  sets constants for CFC surface forcing computation
16   !!----------------------------------------------------------------------
17   USE daymod       ! calendar
18   USE oce_trc      ! Ocean variables
19   USE par_trc      ! TOP parameters
20   USE trc          ! TOP variables
21   USE trdmld_trc_oce
22   USE trdmld_trc
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_sms_cfc       ! called in ???   
28
29   INTEGER , PUBLIC, PARAMETER ::   jpyear = 100   ! temporal parameter
30   INTEGER , PUBLIC, PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres
31   INTEGER , PUBLIC    ::   ndate_beg      ! initial calendar date (aammjj) for CFC
32   INTEGER , PUBLIC    ::   nyear_res      ! restoring time constant (year)
33   INTEGER , PUBLIC    ::   nyear_beg      ! initial year (aa)
34   
35   REAL(wp), PUBLIC, DIMENSION(jpyear,jphem, jp_cfc) ::   p_cfc    ! partial hemispheric pressure for CFC         
36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)              ::   xphem    ! spatial interpolation factor for patm
37   REAL(wp), PUBLIC, DIMENSION(jpi,jpj     ,jp_cfc) ::   qtr_cfc  ! flux at surface
38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj     ,jp_cfc) ::   qint_cfc ! cumulative flux
39
40   REAL(wp), DIMENSION(4,jp_cfc) ::   soa   ! coefficient for solubility of CFC [mol/l/atm]
41   REAL(wp), DIMENSION(3,jp_cfc) ::   sob   !    "               "
42   REAL(wp), DIMENSION(4,jp_cfc) ::   sca   ! coefficients for schmidt number in degre Celcius
43     
44   !                          ! coefficients for conversion
45   REAL(wp) ::   xconv1 = 1.0          ! conversion from to
46   REAL(wp) ::   xconv2 = 0.01/3600.   ! conversion from cm/h to m/s:
47   REAL(wp) ::   xconv3 = 1.0e+3       ! conversion from mol/l/atm to mol/m3/atm
48   REAL(wp) ::   xconv4 = 1.0e-12      ! conversion from mol/m3/atm to mol/m3/pptv
49
50   !! * Substitutions
51#  include "top_substitute.h90"
52   !!----------------------------------------------------------------------
53   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
54   !! $Id$
55   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57
58CONTAINS
59
60   SUBROUTINE trc_sms_cfc( kt )
61      !!----------------------------------------------------------------------
62      !!                     ***  ROUTINE trc_sms_cfc  ***
63      !!
64      !! ** Purpose :   Compute the surface boundary contition on CFC 11
65      !!             passive tracer associated with air-mer fluxes and add it
66      !!             to the general trend of tracers equations.
67      !!
68      !! ** Method  : - get the atmospheric partial pressure - given in pico -
69      !!              - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3)
70      !!              - computation of transfert speed ( given in cm/hour ----> cm/s )
71      !!              - the input function is given by :
72      !!                speed * ( concentration at equilibrium - concentration at surface )
73      !!              - the input function is in pico-mol/m3/s and the
74      !!                CFC concentration in pico-mol/m3
75      !!----------------------------------------------------------------------
76      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
77      !!
78      INTEGER ::   ji, jj, jn, jl, jm, js
79      INTEGER ::   iyear_beg, iyear_end
80      INTEGER ::   im1, im2
81
82      REAL(wp) ::   ztap, zdtap       
83      REAL(wp) ::   zt1, zt2, zt3, zv2
84      REAL(wp) ::   zsol      ! solubility
85      REAL(wp) ::   zsch      ! schmidt number
86      REAL(wp) ::   zpp_cfc   ! atmospheric partial pressure of CFC
87      REAL(wp) ::   zca_cfc   ! concentration at equilibrium
88      REAL(wp) ::   zak_cfc   ! transfert coefficients
89
90      REAL(wp), DIMENSION(jphem,jp_cfc)   ::   zpatm       ! atmospheric function
91      REAL(wp), DIMENSION(jpi,jpj,jpk)    ::   ztrcfc      ! use for CFC sms trend
92      !!----------------------------------------------------------------------
93
94      IF( kt == nittrc000 )   CALL trc_cfc_cst
95
96      ! Temporal interpolation
97      ! ----------------------
98      iyear_beg = nyear + ( nyear_res - 1900 - nyear_beg  )
99      IF ( nmonth <= 6 ) THEN
100         iyear_beg = iyear_beg - 2 + nyear_beg
101         im1       =  6 - nmonth + 1
102         im2       =  6 + nmonth - 1
103      ELSE
104         iyear_beg = iyear_beg - 1 + nyear_beg
105         im1       = 12 - nmonth + 7
106         im2       =      nmonth - 7
107      ENDIF
108      iyear_end = iyear_beg + 1
109
110      !                                                  !------------!
111      DO jl = 1, jp_cfc                                  !  CFC loop  !
112         !                                               !------------!
113         jn = jp_cfc0 + jl - 1
114         ! time interpolation at time kt
115         DO jm = 1, jphem
116            zpatm(jm,jl) = (  p_cfc(iyear_beg, jm, jl) * FLOAT (im1)  &
117               &           +  p_cfc(iyear_end, jm, jl) * FLOAT (im2) ) / 12.
118         END DO
119         
120         !                                                         !------------!
121         DO jj = 1, jpj                                            !  i-j loop  !
122            DO ji = 1, jpi                                         !------------!
123 
124               ! space interpolation
125               zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jl)   &
126                  &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jl)
127
128               ! Computation of concentration at equilibrium : in picomol/l
129               ! coefficient for solubility for CFC-11/12 in  mol/l/atm
130               IF( tmask(ji,jj,1) .GE. 0.5 ) THEN
131                  ztap  = ( tn(ji,jj,1) + 273.16 ) * 0.01
132                  zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) ) 
133                  zsol  =  EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap )   &
134                     &                    + soa(4,jl) * ztap * ztap + sn(ji,jj,1) * zdtap ) 
135               ELSE
136                  zsol  = 0.e0
137               ENDIF
138               ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv   
139               zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) 
140               ! concentration at equilibrium
141               zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)             
142 
143               ! Computation of speed transfert
144               !    Schmidt number
145               zt1  = tn(ji,jj,1)
146               zt2  = zt1 * zt1 
147               zt3  = zt1 * zt2
148               zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3
149
150               !    speed transfert : formulae of wanninkhof 1992
151               zv2     = wndm(ji,jj) * wndm(ji,jj)
152               zsch    = zsch / 660.
153               zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1)
154
155               ! Input function  : speed *( conc. at equil - concen at surface )
156               ! trn in pico-mol/l idem qtr; ak in en m/s
157               qtr_cfc(ji,jj,jl) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc )   &
158#if defined key_off_degrad
159                  &                         * facvol(ji,jj,1)                           &
160#endif
161                  &                         * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) )
162
163               ! Add the surface flux to the trend
164               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr_cfc(ji,jj,jl) / fse3t(ji,jj,1) 
165
166               ! cumulation of surface flux at each time step
167               qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt
168
169# if defined key_trc_diaadd
170               ! Save diagnostics , just for CFC11
171               js = 1 
172               trc2d(ji,jj,jp_cfc0_2d    ) = qtr_cfc (ji,jj,js)
173               trc2d(ji,jj,jp_cfc0_2d + 1) = qint_cfc(ji,jj,js)
174# endif             
175               !                                               !----------------!
176            END DO                                             !  end i-j loop  !
177         END DO                                                !----------------!
178         !                                                  !----------------!
179      END DO                                                !  end CFC loop  !
180      !                                                     !----------------!
181
182      IF( l_trdtrc ) THEN
183          DO jn = jp_cfc0, jp_cfc1
184            ztrcfc(:,:,:) = tra(:,:,:,jn)
185            CALL trd_mod_trc( ztrcfc, jn, jptrc_trd_sms, kt )   ! save trends
186          END DO
187      END IF
188
189   END SUBROUTINE trc_sms_cfc
190
191   SUBROUTINE trc_cfc_cst
192      !!---------------------------------------------------------------------
193      !!                     ***  trc_cfc_cst  *** 
194      !!
195      !! ** Purpose : sets constants for CFC model
196      !!---------------------------------------------------------------------
197
198
199        ! coefficient for CFC11
200        !----------------------
201
202        ! Solubility
203        soa(1,1) = -229.9261 
204        soa(2,1) =  319.6552
205        soa(3,1) =  119.4471
206        soa(4,1) =  -1.39165
207
208        sob(1,1) =  -0.142382
209        sob(2,1) =   0.091459
210        sob(3,1) =  -0.0157274
211
212        ! Schmidt number
213        sca(1,1) = 3501.8
214        sca(2,1) = -210.31
215        sca(3,1) =  6.1851
216        sca(4,1) = -0.07513
217
218        ! coefficient for CFC12
219        !----------------------
220
221        ! Solubility
222        soa(1,2) = -218.0971
223        soa(2,2) =  298.9702
224        soa(3,2) =  113.8049
225        soa(4,2) =  -1.39165
226
227        sob(1,2) =  -0.143566
228        sob(2,2) =   0.091015
229        sob(3,2) =  -0.0153924
230
231        ! schmidt number
232        sca(1,2) =  3845.4 
233        sca(2,2) =  -228.95
234        sca(3,2) =  6.1908 
235        sca(4,2) =  -0.067430
236
237   END SUBROUTINE trc_cfc_cst
238   
239#else
240   !!----------------------------------------------------------------------
241   !!   Dummy module                                         No CFC tracers
242   !!----------------------------------------------------------------------
243CONTAINS
244   SUBROUTINE trc_sms_cfc( kt )       ! Empty routine
245      WRITE(*,*) 'trc_sms_cfc: You should not have seen this print! error?', kt
246   END SUBROUTINE trc_sms_cfc
247#endif
248
249   !!======================================================================
250END MODULE trcsms_cfc
Note: See TracBrowser for help on using the repository browser.