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

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

update modules to take into account the mask land points in NetCDF outputs, see ticket:322

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