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_c14b.F90 in trunk/NEMOGCM/NEMO/TOP_SRC/C14b – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/C14b/trcsms_c14b.F90 @ 3294

Last change on this file since 3294 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

  • Property svn:keywords set to Id
File size: 14.2 KB
Line 
1MODULE trcsms_c14b
2   !!======================================================================
3   !!                      ***  MODULE trcsms_c14b  ***
4   !! TOP : Bomb C14 main module
5   !!======================================================================
6   !! History     -   ! 1994-05 ( J. Orr ) original code
7   !!            1.0  ! 2006-02 ( J.M. Molines )  Free form + modularity
8   !!            2.0  ! 2008-12 ( C. Ethe ) reorganisation
9   !!            4.0  ! 2011-02 ( A.R. Porter, STFC Daresbury ) Dynamic memory
10   !!----------------------------------------------------------------------
11#if defined key_c14b
12   !!----------------------------------------------------------------------
13   !!   'key_c14b'                                         Bomb C14 tracer
14   !!----------------------------------------------------------------------
15   !!   trc_sms_c14b :  compute and add C14 suface forcing to C14 trends
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           ! I/O library
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_sms_c14b       ! called in trcsms.F90
28   PUBLIC   trc_sms_c14b_alloc ! called in trcini_c14b.F90
29
30   INTEGER , PUBLIC, PARAMETER ::   jpmaxrec  = 240           ! temporal parameter
31   INTEGER , PUBLIC, PARAMETER ::   jpmaxrec2 = 2 * jpmaxrec  !
32   INTEGER , PUBLIC, PARAMETER ::   jpzon     = 3             ! number of zones
33
34   INTEGER , PUBLIC    ::   ndate_beg_b      ! initial calendar date (aammjj) for C14
35   INTEGER , PUBLIC    ::   nyear_beg_b      ! initial year for C14
36   INTEGER , PUBLIC    ::   nyear_res_b      ! restoring time constant (year)
37   INTEGER , PUBLIC    ::   nyear_beg        ! initial year (aa)
38
39   REAL(wp), PUBLIC,                    DIMENSION(jpmaxrec,jpzon) ::   bomb       !: C14 atm data (3 zones)
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)          ::   fareaz     !: Spatial Interpolation Factors
41   REAL(wp), PUBLIC,                    DIMENSION(jpmaxrec2)      ::   spco2      !: Atmospheric CO2
42 
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)            ::   qtr_c14    !: flux at surface
44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)            ::   qint_c14   !: cumulative flux
45
46   REAL(wp) ::   xlambda, xdecay, xaccum       ! C14 decay coef. 
47   REAL(wp) ::   xconv1 = 1._wp                ! conversion from to
48   REAL(wp) ::   xconv2 = 0.01_wp / 3600._wp   ! conversion from cm/h to m/s:
49   REAL(wp) ::   xconv3 = 1.e+3_wp             ! conversion from mol/l/atm to mol/m3/atm
50
51   !! * Substitutions
52#  include "top_substitute.h90"
53
54   !!----------------------------------------------------------------------
55   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
56   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/SMS/trcc14bomb.F90,v 1.2 2005/11/14 16:42:43 opalod Exp $
57   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
58   !!----------------------------------------------------------------------
59CONTAINS
60
61   SUBROUTINE trc_sms_c14b( kt )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE trc_sms_c14b  ***
64      !!
65      !! ** Purpose :   Compute the surface boundary contition on C14bomb
66      !!      passive tracer associated with air-mer fluxes and add it to
67      !!      the general trend of tracers equations.
68      !!
69      !! ** Original comments from J. Orr :
70      !!
71      !!      Calculates the input of Bomb C-14 to the surface layer of OPA
72      !!
73      !!      James Orr, LMCE, 28 October 1992
74      !!
75      !!      Initial approach mimics that of Toggweiler, Dixon, & Bryan (1989)
76      !!      (hereafter referred to as TDB) with constant gas exchange,
77      !!      although in this case, a perturbation approach is used for
78      !!      bomb-C14 so that both the ocean and atmosphere begin at zero.
79      !!      This saves tremendous amounts of computer time since no
80      !!      equilibrum run is first required (i.e., for natural C-14).
81      !!      Note: Many sensitivity tests can be run with this approach and
82      !!            one never has to make a run for natural C-14; otherwise,
83      !!            a run for natural C-14 must be run each time that one
84      !!            changes a model parameter!
85      !!
86      !!
87      !!      19 August 1993: Modified to consider Atmospheric C-14 fom IPCC.
88      !!      That is, the IPCC has provided a C-14 atmospheric record (courtesy
89      !!      of Martin Heimann) for model calibration.  This model spans from
90      !!      preindustrial times to present, in a format different than that
91      !!      given by TDB.  It must be converted to the ORR C-14 units used
92      !!      here, although in this case, the perturbation includes not only
93      !!      bomb C-14 but changes due to the Suess effect.
94      !!
95      !!----------------------------------------------------------------------
96      !
97      INTEGER, INTENT(in) ::   kt    ! ocean time-step index
98      !
99      INTEGER :: ji, jj, jk, jz     ! dummy loop indices
100      INTEGER :: iyear_beg , iyear_beg1, iyear_end1 
101      INTEGER :: iyear_beg2, iyear_end2 
102      INTEGER :: imonth1, im1, in1 
103      INTEGER :: imonth2, im2, in2 
104      REAL(wp), DIMENSION(jpzon) :: zonbc14       !: time interp atm C14
105      REAL(wp)                   :: zpco2at       !: time interp atm C02
106      REAL(wp) :: zt, ztp, zsk      ! dummy variables
107      REAL(wp) :: zsol              ! solubility
108      REAL(wp) :: zsch              ! schmidt number
109      REAL(wp) :: zv2               ! wind speed ( square)
110      REAL(wp) :: zpv               ! piston velocity
111      REAL(wp) :: zdemi, ztra
112      REAL(wp), POINTER, DIMENSION(:,:  ) :: zatmbc14 
113      REAL(wp), POINTER, DIMENSION(:,:,:) :: zdecay
114      !!---------------------------------------------------------------------
115      !
116      IF( nn_timing == 1 )  CALL timing_start('trc_sms_c14b')
117      !
118      ! Allocate temporary workspace
119      CALL wrk_alloc( jpi, jpj,      zatmbc14 )
120      CALL wrk_alloc( jpi, jpj, jpk, zdecay   )
121
122      IF( kt == nittrc000 )  THEN         ! Computation of decay coeffcient
123         zdemi   = 5730._wp
124         xlambda = LOG(2.) / zdemi / ( nyear_len(1) * rday )
125         xdecay  = EXP( - xlambda * rdt )
126         xaccum  = 1._wp -  xdecay
127      ENDIF
128
129      ! Temporal interpolation
130      ! ----------------------
131      iyear_beg = nyear - 1954 + ( nyear_res_b - 1700 - nyear_beg_b  ) ! JMM Very dangerous
132                                                                       ! nyear=0001 for 1955
133      ! For Atmospheric C14 concentrations:
134      iyear_beg1 = iyear_beg
135      imonth1    = nmonth
136      IF ( imonth1 <= 6 ) THEN
137         iyear_beg1 = iyear_beg1 - 1
138         im1       =  6 - imonth1 + 1
139         im2       =  6 + imonth1 - 1
140      ELSE
141         im1       = 12 - imonth1 + 7
142         im2       =      imonth1 - 7
143      ENDIF
144      iyear_end1 = iyear_beg1 + 1
145
146      iyear_beg1 = MAX( iyear_beg1, 1   )
147      iyear_end1 = MIN( iyear_end1, 241 )
148
149
150      ! For Atmospheric CO2 concentrations:
151      iyear_beg2 = 2 * iyear_beg - 1
152      imonth2    = INT( nmonth / 2. )
153
154      IF ( imonth2 <= 3 ) THEN
155         iyear_beg2 = iyear_beg2 - 1 
156         in1       = 3 - imonth2 + 1
157         in2       = 3 + imonth2 - 1
158      ELSE
159         in1       = 6 - imonth2 + 4
160         in2       =     imonth2 - 4
161      ENDIF
162     
163      iyear_end2 = iyear_beg2 + 1
164     
165      iyear_beg2 = MAX( iyear_beg2, 1   )
166      iyear_end2 = MIN( iyear_end2, 482 )
167
168
169      !  ----------------------------------------------------------------
170      !  As explained by the TDB 89 papers, C-14/C-12 is the same
171      !  as C-14 concentration in this special case (no fractionation
172      !  effects in this model, which thus allow direct comparison
173      !  to del-C-14, after unit change from above).
174      ! -----------------------------------------------------------------------
175      !  Calc C-14 in atmosphere based on interp of IPCC (M. Heimann) data
176      !        - Compare input to calculated C-14 for each time in record
177      !-------------------------------------------------------------------------
178     
179     
180      !  Temporal and spatial interpolation at time k
181      ! --------------------------------------------------
182     
183      ! Compute atmospheric C-14 for each zone (90-20S, 20S-20N, 20-90N)
184      DO jz = 1, jpzon
185         zonbc14(jz) = (  bomb(iyear_beg1,jz) * FLOAT( im1 )  &
186              &         + bomb(iyear_end1,jz) * FLOAT( im2 ) ) / 12.
187         ! C-14 exactly starts at zero :
188         ! JMM +Zouhair : Slightly negative values are set to 0 (when perturbation approaches)
189         zonbc14(jz) = MAX( zonbc14(jz), 0. )
190      END DO
191     
192     
193      !  For each (i,j)-box, with information from the fractional area
194      !  (zonmean), computes area-weighted mean to give the atmospheric C-14
195      !  ----------------------------------------------------------------
196      zatmbc14(:,:) = zonbc14(1) * fareaz(:,:,1)   &
197         &          + zonbc14(2) * fareaz(:,:,2)   &
198         &          + zonbc14(3) * fareaz(:,:,3)
199     
200      ! time interpolation of CO2 concentrations to it time step 
201      zpco2at = (  spco2(iyear_beg2) * FLOAT( in1 )              &
202           &     + spco2(iyear_end2) * FLOAT( in2 ) ) / 6.
203
204      IF(lwp) THEN
205          WRITE(numout, *) 'time : ', kt, ' CO2 year begin/end :',iyear_beg2,'/',iyear_end2,   &
206          &                ' CO2 concen : ',zpco2at 
207          WRITE(numout, *) 'time : ', kt, ' C14 year begin/end :',iyear_beg1,'/',iyear_end1,   &
208          &                ' C14B concen (Z1/Z2/Z3) : ',zonbc14(1),'/',zonbc14(2),'/',zonbc14(3)
209      ENDIF
210
211      !  Determine seasonally variable gas exchange coefficient
212      !----------------------------------------------------------
213      !  Computes the Schmidt number of CO2 in seawater using the formulation
214      !  presented by Wanninkhof (1992, J. Geophys. Res., 97,7373-7382). 
215      ! -------------------------------------------------------------------
216      DO jj = 1, jpj
217         DO ji = 1, jpi 
218            !  Computation of solubility 
219            IF (tmask(ji,jj,1) >  0.) THEN
220               ztp  = ( tsn(ji,jj,1,jp_tem) + 273.16 ) * 0.01
221               zsk  = 0.023517 + ztp * ( -0.023656 + 0.0047036 * ztp )
222               zsol = EXP( -60.2409 + 93.4517 / ztp  + 23.3585 * LOG( ztp ) + zsk * tsn(ji,jj,1,jp_sal) )
223               ! convert solubilities [mol/(l * atm)] -> [mol/(m^3 * ppm)]
224               zsol = zsol * 1.e-03
225            ELSE
226               zsol = 0._wp
227            ENDIF
228
229            ! speed transfert : Formulation of Wanninkhof (1992, JGR, 97,7373-7382)
230            ! JMM/Zouhair : coef of 0.25 rather than 0.3332 for CORe wind speed
231
232            ! Computes the Schmidt number of CO2 in seawater
233            zt   = tsn(ji,jj,1,jp_tem)
234            zsch = 2073.1 + zt * ( -125.62 + zt * (3.6276 - 0.043219 * zt ) )
235
236            ! Wanninkhof Piston velocity and convert from units [cm/hr] -> [m/s]
237            zv2  = wndm(ji,jj) * wndm(ji,jj)
238            zsch = zsch / 660.
239            zpv  = ( 0.25  * zv2 / SQRT(zsch) ) * xconv2 * tmask(ji,jj,1)
240
241            ! Flux of Bomb C-14 from air-sea : speed*(conc. at equil-conc. at surf)
242            ! in C-14 (orr-model-units) / m**2 * s
243            qtr_c14(ji,jj) = -zpv * zsol * zpco2at                                   &
244                 &                       * ( trb(ji,jj,1,jpc14) - zatmbc14(ji,jj) )  &
245#if defined key_degrad
246                 &                       * facvol(ji,jj,1)                           &
247#endif
248                  &                      * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) ) / 2.
249            ! Add the surface flux to the trend
250            tra(ji,jj,1,jpc14) = tra(ji,jj,1,jpc14) + qtr_c14(ji,jj) / fse3t(ji,jj,1) 
251           
252            ! cumulation of surface flux at each time step
253            qint_c14(ji,jj) = qint_c14(ji,jj) + qtr_c14(ji,jj) * rdt
254            !
255         END DO
256      END DO
257
258      ! Computation of decay effects on tracer concentration
259      DO jk = 1, jpk
260         DO jj = 1, jpj
261            DO ji = 1, jpi
262#if defined key_degrad
263               zdecay(ji,jj,jk) = trn(ji,jj,jk,jpc14) * ( 1. - EXP( -xlambda * rdt * facvol(ji,jj,jk) ) )
264#else
265               zdecay(ji,jj,jk) = trn(ji,jj,jk,jpc14) * xaccum
266#endif
267               tra(ji,jj,jk,jpc14) = tra(ji,jj,jk,jpc14) - zdecay(ji,jj,jk) / rdt
268               !
269            END DO
270         END DO
271      END DO
272
273      IF( ln_diatrc ) THEN
274         IF( lk_iomput ) THEN
275            CALL iom_put( "qtrC14b"  , qtr_c14  )
276            CALL iom_put( "qintC14b" , qint_c14 )
277            CALL iom_put( "fdecay"   , zdecay   )
278          ELSE
279            trc2d(:,:  ,jp_c14b0_2d     ) = qtr_c14 (:,:)
280            trc2d(:,:  ,jp_c14b0_2d + 1 ) = qint_c14(:,:)
281            trc3d(:,:,:,jp_c14b0_3d     ) = zdecay  (:,:,:)
282          ENDIF
283      ENDIF
284
285      IF( l_trdtrc )  CALL trd_mod_trc( tra(:,:,:,jpc14), jpc14, jptra_trd_sms, kt )   ! save trends
286
287      CALL wrk_dealloc( jpi, jpj,      zatmbc14 )
288      CALL wrk_dealloc( jpi, jpj, jpk, zdecay   )
289      !
290      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_c14b')
291      !
292   END SUBROUTINE trc_sms_c14b
293
294
295   INTEGER FUNCTION trc_sms_c14b_alloc()
296      !!----------------------------------------------------------------------
297      !!                  ***  ROUTINE trc_sms_c14b_alloc  ***
298      !!----------------------------------------------------------------------
299      ALLOCATE( fareaz  (jpi,jpj ,jpzon) ,     &
300         &      qtr_c14 (jpi,jpj)        ,     &
301         &      qint_c14(jpi,jpj)        , STAT=trc_sms_c14b_alloc )
302         !
303      IF( trc_sms_c14b_alloc /= 0 )   CALL ctl_warn('trc_sms_c14b_alloc: failed to allocate arrays')
304      !
305   END FUNCTION trc_sms_c14b_alloc
306
307#else
308   !!----------------------------------------------------------------------
309   !!   Default option                                         Dummy module
310   !!----------------------------------------------------------------------
311CONTAINS
312   SUBROUTINE trc_sms_c14b( kt )       ! Empty routine
313      WRITE(*,*) 'trc_freons: You should not have seen this print! error?', kt
314   END SUBROUTINE trc_sms_c14b
315#endif
316
317  !!======================================================================
318END MODULE trcsms_c14b
Note: See TracBrowser for help on using the repository browser.