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 branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90 @ 2643

Last change on this file since 2643 was 2643, checked in by cetlod, 13 years ago

Changed TOP/PISCES to use dynamic memory & improve the others TOP modules

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