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

source: trunk/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90 @ 6361

Last change on this file since 6361 was 6140, checked in by timgraham, 9 years ago

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

  • Property svn:keywords set to Id
File size: 12.4 KB
RevLine 
[933]1MODULE trcsms_cfc
2   !!======================================================================
3   !!                      ***  MODULE trcsms_cfc  ***
4   !! TOP : CFC main model
5   !!======================================================================
[2715]6   !! History :  OPA  !  1999-10  (JC. Dutay)  original code
7   !!  NEMO      1.0  !  2004-03  (C. Ethe) free form + modularity
8   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation
[933]9   !!----------------------------------------------------------------------
10#if defined key_cfc
11   !!----------------------------------------------------------------------
12   !!   'key_cfc'                                               CFC tracers
13   !!----------------------------------------------------------------------
[2715]14   !!   trc_sms_cfc  :  compute and add CFC suface forcing to CFC trends
[3680]15   !!   cfc_init     :  sets constants for CFC surface forcing computation
[933]16   !!----------------------------------------------------------------------
[2715]17   USE oce_trc       ! Ocean variables
18   USE par_trc       ! TOP parameters
19   USE trc           ! TOP variables
[4990]20   USE trd_oce
21   USE trdtrc
[2715]22   USE iom           ! I/O library
[933]23
24   IMPLICIT NONE
25   PRIVATE
26
[2715]27   PUBLIC   trc_sms_cfc         ! called in ???   
28   PUBLIC   trc_sms_cfc_alloc   ! called in trcini_cfc.F90
[933]29
30   INTEGER , PUBLIC, PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres
[3294]31   INTEGER , PUBLIC            ::   jpyear         ! Number of years read in CFC1112 file
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)
[933]35   
[3294]36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   p_cfc    ! partial hemispheric pressure for CFC
[2715]37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   xphem    ! spatial interpolation factor for patm
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_cfc  ! flux at surface
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qint_cfc ! cumulative flux
[3294]40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   patm     ! atmospheric function
[933]41
[2423]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
[933]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   !!----------------------------------------------------------------------
[2528]53   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[1146]54   !! $Id$
[2715]55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[933]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      !!----------------------------------------------------------------------
[2715]75      INTEGER, INTENT(in) ::   kt    ! ocean time-step index
76      !
77      INTEGER  ::   ji, jj, jn, jl, jm, js
78      INTEGER  ::   iyear_beg, iyear_end
[3294]79      INTEGER  ::   im1, im2, ierr
[933]80      REAL(wp) ::   ztap, zdtap       
81      REAL(wp) ::   zt1, zt2, zt3, zv2
82      REAL(wp) ::   zsol      ! solubility
83      REAL(wp) ::   zsch      ! schmidt number
84      REAL(wp) ::   zpp_cfc   ! atmospheric partial pressure of CFC
85      REAL(wp) ::   zca_cfc   ! concentration at equilibrium
86      REAL(wp) ::   zak_cfc   ! transfert coefficients
[3294]87      REAL(wp), ALLOCATABLE, DIMENSION(:,:)  ::   zpatm     ! atmospheric function
[933]88      !!----------------------------------------------------------------------
[2715]89      !
[3294]90      !
91      IF( nn_timing == 1 )  CALL timing_start('trc_sms_cfc')
92      !
93      ALLOCATE( zpatm(jphem,jp_cfc), STAT=ierr )
94      IF( ierr > 0 ) THEN
95         CALL ctl_stop( 'trc_sms_cfc: unable to allocate zpatm array' )   ;   RETURN
[2715]96      ENDIF
[933]97
[3680]98      IF( kt == nittrc000 )   CALL cfc_init
[933]99
100      ! Temporal interpolation
101      ! ----------------------
[2047]102      iyear_beg = nyear - 1900
[933]103      IF ( nmonth <= 6 ) THEN
[2047]104         iyear_beg = iyear_beg - 1
[933]105         im1       =  6 - nmonth + 1
106         im2       =  6 + nmonth - 1
107      ELSE
108         im1       = 12 - nmonth + 7
109         im2       =      nmonth - 7
110      ENDIF
111      iyear_end = iyear_beg + 1
112
[1255]113      !                                                  !------------!
114      DO jl = 1, jp_cfc                                  !  CFC loop  !
115         !                                               !------------!
116         jn = jp_cfc0 + jl - 1
[933]117         ! time interpolation at time kt
118         DO jm = 1, jphem
[1255]119            zpatm(jm,jl) = (  p_cfc(iyear_beg, jm, jl) * FLOAT (im1)  &
120               &           +  p_cfc(iyear_end, jm, jl) * FLOAT (im2) ) / 12.
[933]121         END DO
122         
123         !                                                         !------------!
124         DO jj = 1, jpj                                            !  i-j loop  !
125            DO ji = 1, jpi                                         !------------!
126 
127               ! space interpolation
[1255]128               zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jl)   &
129                  &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jl)
[933]130
131               ! Computation of concentration at equilibrium : in picomol/l
132               ! coefficient for solubility for CFC-11/12 in  mol/l/atm
133               IF( tmask(ji,jj,1) .GE. 0.5 ) THEN
[2528]134                  ztap  = ( tsn(ji,jj,1,jp_tem) + 273.16 ) * 0.01
[1255]135                  zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) ) 
136                  zsol  =  EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap )   &
[2528]137                     &                    + soa(4,jl) * ztap * ztap + tsn(ji,jj,1,jp_sal) * zdtap ) 
[933]138               ELSE
139                  zsol  = 0.e0
140               ENDIF
141               ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv   
142               zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) 
143               ! concentration at equilibrium
144               zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)             
145 
146               ! Computation of speed transfert
147               !    Schmidt number
[2528]148               zt1  = tsn(ji,jj,1,jp_tem)
[933]149               zt2  = zt1 * zt1 
150               zt3  = zt1 * zt2
[1255]151               zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3
[933]152
153               !    speed transfert : formulae of wanninkhof 1992
[1004]154               zv2     = wndm(ji,jj) * wndm(ji,jj)
[933]155               zsch    = zsch / 660.
156               zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1)
157
158               ! Input function  : speed *( conc. at equil - concen at surface )
[3294]159               ! trn in pico-mol/l idem qtr; ak in en m/a
[1255]160               qtr_cfc(ji,jj,jl) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc )   &
[2528]161#if defined key_degrad
[1255]162                  &                         * facvol(ji,jj,1)                           &
[933]163#endif
[1255]164                  &                         * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) )
[933]165               ! Add the surface flux to the trend
[6140]166               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr_cfc(ji,jj,jl) / e3t_n(ji,jj,1) 
[933]167
168               ! cumulation of surface flux at each time step
[1255]169               qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt
[933]170               !                                               !----------------!
171            END DO                                             !  end i-j loop  !
172         END DO                                                !----------------!
173         !                                                  !----------------!
174      END DO                                                !  end CFC loop  !
[3680]175      !
176      IF( lrst_trc ) THEN
177         IF(lwp) WRITE(numout,*)
178         IF(lwp) WRITE(numout,*) 'trc_sms_cfc : cumulated input function fields written in ocean restart file ',   &
179            &                    'at it= ', kt,' date= ', ndastp
180         IF(lwp) WRITE(numout,*) '~~~~'
181         DO jn = jp_cfc0, jp_cfc1
182            CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) )
183         END DO
[4996]184      ENDIF                                           
185      !
186      IF( lk_iomput ) THEN
187         CALL iom_put( "qtrCFC11"  , qtr_cfc (:,:,1) )
188         CALL iom_put( "qintCFC11" , qint_cfc(:,:,1) )
189      ELSE
190         IF( ln_diatrc ) THEN
191            trc2d(:,:,jp_cfc0_2d    ) = qtr_cfc (:,:,1)
192            trc2d(:,:,jp_cfc0_2d + 1) = qint_cfc(:,:,1)
193         END IF
[3294]194      END IF
[4996]195      !
[1255]196      IF( l_trdtrc ) THEN
197          DO jn = jp_cfc0, jp_cfc1
[4990]198            CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt )   ! save trends
[1255]199          END DO
200      END IF
[2715]201      !
[3294]202      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_cfc')
[2715]203      !
[933]204   END SUBROUTINE trc_sms_cfc
205
[2715]206
[3680]207   SUBROUTINE cfc_init
[933]208      !!---------------------------------------------------------------------
[3680]209      !!                     ***  cfc_init  *** 
[933]210      !!
211      !! ** Purpose : sets constants for CFC model
212      !!---------------------------------------------------------------------
[3680]213      INTEGER :: jn
[933]214
[2715]215      ! coefficient for CFC11
216      !----------------------
[933]217
[2715]218      ! Solubility
219      soa(1,1) = -229.9261 
220      soa(2,1) =  319.6552
221      soa(3,1) =  119.4471
222      soa(4,1) =  -1.39165
[933]223
[2715]224      sob(1,1) =  -0.142382
225      sob(2,1) =   0.091459
226      sob(3,1) =  -0.0157274
[933]227
[2715]228      ! Schmidt number
229      sca(1,1) = 3501.8
230      sca(2,1) = -210.31
231      sca(3,1) =  6.1851
232      sca(4,1) = -0.07513
[1004]233
[2715]234      ! coefficient for CFC12
235      !----------------------
[1004]236
[2715]237      ! Solubility
238      soa(1,2) = -218.0971
239      soa(2,2) =  298.9702
240      soa(3,2) =  113.8049
241      soa(4,2) =  -1.39165
[1255]242
[2715]243      sob(1,2) =  -0.143566
244      sob(2,2) =   0.091015
245      sob(3,2) =  -0.0153924
[1255]246
[2715]247      ! schmidt number
248      sca(1,2) =  3845.4 
249      sca(2,2) =  -228.95
250      sca(3,2) =  6.1908 
251      sca(4,2) =  -0.067430
[1255]252
[3680]253      IF( ln_rsttr ) THEN
254         IF(lwp) WRITE(numout,*)
255         IF(lwp) WRITE(numout,*) ' Read specific variables from CFC model '
256         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
257         !
258         DO jn = jp_cfc0, jp_cfc1
259            CALL iom_get( numrtr, jpdom_autoglo, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) 
260         END DO
261      ENDIF
262      IF(lwp) WRITE(numout,*)
263      !
264   END SUBROUTINE cfc_init
[1255]265
[2715]266
267   INTEGER FUNCTION trc_sms_cfc_alloc()
268      !!----------------------------------------------------------------------
269      !!                     ***  ROUTINE trc_sms_cfc_alloc  ***
270      !!----------------------------------------------------------------------
271      ALLOCATE( xphem   (jpi,jpj)        ,     &
272         &      qtr_cfc (jpi,jpj,jp_cfc) ,     &
273         &      qint_cfc(jpi,jpj,jp_cfc) , STAT=trc_sms_cfc_alloc )
274         !
275      IF( trc_sms_cfc_alloc /= 0 ) CALL ctl_warn('trc_sms_cfc_alloc : failed to allocate arrays.')
276      !
277   END FUNCTION trc_sms_cfc_alloc
278
[933]279#else
280   !!----------------------------------------------------------------------
281   !!   Dummy module                                         No CFC tracers
282   !!----------------------------------------------------------------------
283CONTAINS
284   SUBROUTINE trc_sms_cfc( kt )       ! Empty routine
285      WRITE(*,*) 'trc_sms_cfc: You should not have seen this print! error?', kt
286   END SUBROUTINE trc_sms_cfc
287#endif
288
289   !!======================================================================
290END MODULE trcsms_cfc
Note: See TracBrowser for help on using the repository browser.