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.
p4zflx.F90 in branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES – NEMO

source: branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zflx.F90 @ 2504

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

Computation of monthly mean ocean carbon flux in PISCES

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 10.8 KB
Line 
1MODULE p4zflx
2   !!======================================================================
3   !!                         ***  MODULE p4zflx  ***
4   !! TOP :   PISCES CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
5   !!======================================================================
6   !! History :    -   !  1988-07  (E. MAIER-REIMER) Original code
7   !!              -   !  1998     (O. Aumont) additions
8   !!              -   !  1999     (C. Le Quere) modifications
9   !!             1.0  !  2004     (O. Aumont) modifications
10   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
11   !!----------------------------------------------------------------------
12#if defined key_pisces
13   !!----------------------------------------------------------------------
14   !!   'key_pisces'                                       PISCES bio-model
15   !!----------------------------------------------------------------------
16   !!   p4z_flx       :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
17   !!   p4z_flx_init  :   Read the namelist
18   !!----------------------------------------------------------------------
19   USE trc
20   USE oce_trc         !
21   USE trc
22   USE sms_pisces
23   USE prtctl_trc
24   USE p4zche
25   USE iom
26#if defined key_cpl_carbon_cycle
27   USE sbc_oce , ONLY :  atm_co2
28#endif
29   USE lib_mpp
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   p4z_flx 
35
36   REAL(wp) :: &  ! pre-industrial atmospheric [co2] (ppm) 
37      atcox  = 0.20946 ,    &  !:
38      atcco2 = 278.            !:
39
40   REAL(wp) :: &
41      xconv  = 0.01/3600      !: coefficients for conversion
42
43   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  oce_co2            !: ocean carbon flux
44   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  satmco2            !: atmospheric pco2
45   REAL(wp)                             ::  t_oce_co2_flx      !: Total ocean carbon flux
46   REAL(wp)                             ::  t_atm_co2_flx      !: global mean of atmospheric pco2
47   REAL(wp)                             ::  area               !: ocean surface
48
49   !!* Substitution
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 p4z_flx ( kt )
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE p4z_flx  ***
62      !!
63      !! ** Purpose :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
64      !!
65      !! ** Method  : - ???
66      !!---------------------------------------------------------------------
67      INTEGER, INTENT(in) :: kt
68      INTEGER  ::   ji, jj, jrorr
69      REAL(wp) ::   ztc, ztc2, ztc3, zws, zkgwan
70      REAL(wp) ::   zfld, zflu, zfld16, zflu16, zfact
71      REAL(wp) ::   zph, zah2, zbot, zdic, zalk, zsch_o2, zalka, zsch_co2
72      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3
73#if defined key_trc_diaadd && defined key_iomput
74      REAL(wp), DIMENSION(jpi,jpj) ::  zcflx, zoflx, zkg, zdpco2, zdpo2
75#endif
76      CHARACTER (len=25) :: charout
77
78      !!---------------------------------------------------------------------
79
80
81      IF( kt == nittrc000  )   CALL p4z_flx_init      ! Initialization (first time-step only)
82
83      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN
84      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION
85      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2
86
87#if defined key_cpl_carbon_cycle
88      satmco2(:,:) = atm_co2(:,:)
89#endif
90
91      DO jrorr = 1, 10
92
93!CDIR NOVERRCHK
94         DO jj = 1, jpj
95!CDIR NOVERRCHK
96            DO ji = 1, jpi
97
98               ! DUMMY VARIABLES FOR DIC, H+, AND BORATE
99               zbot  = borat(ji,jj,1)
100               zfact = rhop(ji,jj,1) / 1000. + rtrn
101               zdic  = trn(ji,jj,1,jpdic) / zfact
102               zph   = MAX( hi(ji,jj,1), 1.e-10 ) / zfact
103               zalka = trn(ji,jj,1,jptal) / zfact
104
105               ! CALCULATE [ALK]([CO3--], [HCO3-])
106               zalk  = zalka - (  akw3(ji,jj,1) / zph - zph + zbot / ( 1.+ zph / akb3(ji,jj,1) )  )
107
108               ! CALCULATE [H+] AND [H2CO3]
109               zah2   = SQRT(  (zdic-zalk)**2 + 4.* ( zalk * ak23(ji,jj,1)   &
110                  &                                        / ak13(ji,jj,1) ) * ( 2.* zdic - zalk )  )
111               zah2   = 0.5 * ak13(ji,jj,1) / zalk * ( ( zdic - zalk ) + zah2 )
112               zh2co3(ji,jj) = ( 2.* zdic - zalk ) / ( 2.+ ak13(ji,jj,1) / zah2 ) * zfact
113               hi(ji,jj,1)   = zah2 * zfact
114            END DO
115         END DO
116      END DO
117
118
119      ! --------------
120      ! COMPUTE FLUXES
121      ! --------------
122
123      ! FIRST COMPUTE GAS EXCHANGE COEFFICIENTS
124      ! -------------------------------------------
125
126!CDIR NOVERRCHK
127      DO jj = 1, jpj
128!CDIR NOVERRCHK
129         DO ji = 1, jpi
130            ztc  = MIN( 35., tn(ji,jj,1) )
131            ztc2 = ztc * ztc
132            ztc3 = ztc * ztc2 
133            ! Compute the schmidt Number both O2 and CO2
134            zsch_co2 = 2073.1 - 125.62 * ztc + 3.6276 * ztc2 - 0.043126 * ztc3
135            zsch_o2  = 1953.4 - 128.0  * ztc + 3.9918 * ztc2 - 0.050091 * ztc3
136            !  wind speed
137            zws  = wndm(ji,jj) * wndm(ji,jj)
138            ! Compute the piston velocity for O2 and CO2
139            zkgwan = 0.3 * zws  + 2.5 * ( 0.5246 + 0.016256 * ztc + 0.00049946  * ztc2 )
140# if defined key_off_degrad
141            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1) * facvol(ji,jj,1)
142#else
143            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1)
144#endif 
145            ! compute gas exchange for CO2 and O2
146            zkgco2(ji,jj) = zkgwan * SQRT( 660./ zsch_co2 )
147            zkgo2 (ji,jj) = zkgwan * SQRT( 660./ zsch_o2 )
148         END DO
149      END DO
150
151      DO jj = 1, jpj
152         DO ji = 1, jpi
153            ! Compute CO2 flux for the sea and air
154            zfld = satmco2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj)
155            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj)
156            oce_co2(ji,jj) = ( zfld - zflu ) * rfact &
157               &             * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000.
158            ! compute the trend
159            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1)
160
161            ! Compute O2 flux
162            zfld16 = atcox * chemc(ji,jj,2) * tmask(ji,jj,1) * zkgo2(ji,jj)
163            zflu16 = trn(ji,jj,1,jpoxy) * tmask(ji,jj,1) * zkgo2(ji,jj)
164            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + ( zfld16 - zflu16 ) / fse3t(ji,jj,1)
165
166#if defined key_trc_diaadd 
167            ! Save diagnostics
168#  if ! defined key_iomput
169            trc2d(ji,jj,jp_pcs0_2d    ) = ( zfld - zflu )     * 1000. * tmask(ji,jj,1)
170            trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1)
171            trc2d(ji,jj,jp_pcs0_2d + 2) = zkgco2(ji,jj) * tmask(ji,jj,1)
172            trc2d(ji,jj,jp_pcs0_2d + 3) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) &
173               &                            * tmask(ji,jj,1)
174#  else
175            zcflx(ji,jj) = ( zfld - zflu ) * 1000.  * tmask(ji,jj,1)
176            zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1)
177            zkg  (ji,jj) = zkgco2(ji,jj) * tmask(ji,jj,1)
178            zdpco2(ji,jj) = ( satmco2(ji,jj) - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) * tmask(ji,jj,1)
179            zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) * tmask(ji,jj,1)
180#  endif
181#endif
182         END DO
183      END DO
184
185      t_oce_co2_flx = t_oce_co2_flx + SUM( oce_co2(:,:) * tmask_i(:,:) )           ! Cumulative Total Flux of Carbon
186      IF( kt == nitend ) THEN
187         t_atm_co2_flx = SUM( satmco2(:,:) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  ! Total atmospheric pCO2
188         !
189         IF( lk_mpp ) THEN                                                         ! sum over the global domain
190           CALL mpp_sum( t_atm_co2_flx )   
191           CALL mpp_sum( t_oce_co2_flx )   
192         ENDIF
193         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15                      ! Conversion in PgC ; negative for out of the ocean
194         t_atm_co2_flx = t_atm_co2_flx  / area                                     ! global mean of atmospheric pCO2
195         !
196         IF( lwp) THEN
197            WRITE(numout,*)
198            WRITE(numout,*) ' Global mean of atmospheric pCO2 (ppm) at it= ', kt, ' date= ', ndastp, ' : ',t_atm_co2_flx
199            WRITE(numout,*) 
200            WRITE(numout,*) ' Cumulative total Flux of Carbon out of the ocean (PgC) :' , t_oce_co2_flx
201            WRITE(numout,*) 
202         ENDIF
203         !
204      ENDIF
205
206      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
207         WRITE(charout, FMT="('flx ')")
208         CALL prt_ctl_trc_info(charout)
209         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
210      ENDIF
211
212# if defined key_trc_diaadd && defined key_iomput
213      CALL iom_put( "Cflx" , zcflx  )
214      CALL iom_put( "Oflx" , zoflx  )
215      CALL iom_put( "Kg"   , zkg    )
216      CALL iom_put( "Dpco2", zdpco2 )
217      CALL iom_put( "Dpo2" , zdpo2  )
218#endif
219
220   END SUBROUTINE p4z_flx
221
222   SUBROUTINE p4z_flx_init
223
224      !!----------------------------------------------------------------------
225      !!                  ***  ROUTINE p4z_flx_init  ***
226      !!
227      !! ** Purpose :   Initialization of atmospheric conditions
228      !!
229      !! ** Method  :   Read the nampisext namelist and check the parameters
230      !!      called at the first timestep (nittrc000)
231      !! ** input   :   Namelist nampisext
232      !!
233      !!----------------------------------------------------------------------
234
235      NAMELIST/nampisext/ atcco2
236
237      REWIND( numnat )                     ! read numnat
238      READ  ( numnat, nampisext )
239
240      IF(lwp) THEN                         ! control print
241         WRITE(numout,*) ' '
242         WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext'
243         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
244         WRITE(numout,*) '    Atmospheric pCO2      atcco2      =', atcco2
245      ENDIF
246
247      ! interior global domain surface
248      area = SUM( e1t(:,:) * e2t(:,:) * tmask_i(:,:) )
249      IF( lk_mpp ) CALL mpp_sum( area )
250
251      ! Initialization of Flux of Carbon
252      oce_co2(:,:) = 0.
253      t_atm_co2_flx = 0.
254      ! Initialisation of atmospheric pco2
255      satmco2(:,:) = atcco2
256      t_oce_co2_flx = 0.
257
258   END SUBROUTINE p4z_flx_init
259
260#else
261   !!======================================================================
262   !!  Dummy module :                                   No PISCES bio-model
263   !!======================================================================
264CONTAINS
265   SUBROUTINE p4z_flx( kt )                   ! Empty routine
266      INTEGER, INTENT( in ) ::   kt
267      WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt
268   END SUBROUTINE p4z_flx
269#endif 
270
271   !!======================================================================
272END MODULE  p4zflx
Note: See TracBrowser for help on using the repository browser.