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

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/C14b/trcsms_c14b.F90 @ 2633

Last change on this file since 2633 was 2633, checked in by trackstand2, 13 years ago

Renamed wrk_use => wrk_in_use and wrk_release => wrk_not_released

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