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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zflx.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

  • 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   PUBLIC   p4z_flx_init 
36
37   REAL(wp) :: &  ! pre-industrial atmospheric [co2] (ppm) 
38      atcox  = 0.20946 ,    &  !:
39      atcco2 = 278.            !:
40
41   REAL(wp) :: &
42      xconv  = 0.01/3600      !: coefficients for conversion
43
44   INTEGER  ::  nspyr         !: number of timestep per year
45
46#if defined key_cpl_carbon_cycle
47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  &
48      oce_co2            !: ocean carbon flux
49   REAL(wp) :: &
50      t_atm_co2_flx,  &  !: Total atmospheric carbon flux per year
51      t_oce_co2_flx      !: Total ocean carbon flux per year
52#endif
53
54   !!* Substitution
55#  include "top_substitute.h90"
56   !!----------------------------------------------------------------------
57   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
58   !! $Id$
59   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
60   !!----------------------------------------------------------------------
61
62CONTAINS
63
64   SUBROUTINE p4z_flx ( kt )
65      !!---------------------------------------------------------------------
66      !!                     ***  ROUTINE p4z_flx  ***
67      !!
68      !! ** Purpose :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
69      !!
70      !! ** Method  : - ???
71      !!---------------------------------------------------------------------
72      INTEGER, INTENT(in) :: kt
73      INTEGER  ::   ji, jj, jrorr
74      REAL(wp) ::   ztc, ztc2, ztc3, zws, zkgwan
75      REAL(wp) ::   zfld, zflu, zfld16, zflu16, zfact
76      REAL(wp) ::   zph, zah2, zbot, zdic, zalk, zsch_o2, zalka, zsch_co2
77      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3
78#if defined key_diatrc && defined key_iomput
79      REAL(wp), DIMENSION(jpi,jpj) ::  zcflx, zoflx, zkg, zdpco2, zdpo2
80#endif
81      CHARACTER (len=25) :: charout
82
83      !!---------------------------------------------------------------------
84
85      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN
86      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION
87      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2
88
89      DO jrorr = 1, 10
90
91!CDIR NOVERRCHK
92         DO jj = 1, jpj
93!CDIR NOVERRCHK
94            DO ji = 1, jpi
95
96               ! DUMMY VARIABLES FOR DIC, H+, AND BORATE
97               zbot  = borat(ji,jj,1)
98               zfact = rhop(ji,jj,1) / 1000. + rtrn
99               zdic  = trn(ji,jj,1,jpdic) / zfact
100               zph   = MAX( hi(ji,jj,1), 1.e-10 ) / zfact
101               zalka = trn(ji,jj,1,jptal) / zfact
102
103               ! CALCULATE [ALK]([CO3--], [HCO3-])
104               zalk  = zalka - (  akw3(ji,jj,1) / zph - zph + zbot / ( 1.+ zph / akb3(ji,jj,1) )  )
105
106               ! CALCULATE [H+] AND [H2CO3]
107               zah2   = SQRT(  (zdic-zalk)**2 + 4.* ( zalk * ak23(ji,jj,1)   &
108                  &                                        / ak13(ji,jj,1) ) * ( 2.* zdic - zalk )  )
109               zah2   = 0.5 * ak13(ji,jj,1) / zalk * ( ( zdic - zalk ) + zah2 )
110               zh2co3(ji,jj) = ( 2.* zdic - zalk ) / ( 2.+ ak13(ji,jj,1) / zah2 ) * zfact
111               hi(ji,jj,1)   = zah2 * zfact
112            END DO
113         END DO
114      END DO
115
116
117      ! --------------
118      ! COMPUTE FLUXES
119      ! --------------
120
121      ! FIRST COMPUTE GAS EXCHANGE COEFFICIENTS
122      ! -------------------------------------------
123
124!CDIR NOVERRCHK
125      DO jj = 1, jpj
126!CDIR NOVERRCHK
127         DO ji = 1, jpi
128            ztc  = MIN( 35., tsn(ji,jj,1,jp_tem) )
129            ztc2 = ztc * ztc
130            ztc3 = ztc * ztc2 
131            ! Compute the schmidt Number both O2 and CO2
132            zsch_co2 = 2073.1 - 125.62 * ztc + 3.6276 * ztc2 - 0.043126 * ztc3
133            zsch_o2  = 1953.4 - 128.0  * ztc + 3.9918 * ztc2 - 0.050091 * ztc3
134            !  wind speed
135            zws  = wndm(ji,jj) * wndm(ji,jj)
136            ! Compute the piston velocity for O2 and CO2
137            zkgwan = 0.3 * zws  + 2.5 * ( 0.5246 + 0.016256 * ztc + 0.00049946  * ztc2 )
138# if defined key_degrad
139            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1) * facvol(ji,jj,1)
140#else
141            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1)
142#endif 
143            ! compute gas exchange for CO2 and O2
144            zkgco2(ji,jj) = zkgwan * SQRT( 660./ zsch_co2 )
145            zkgo2 (ji,jj) = zkgwan * SQRT( 660./ zsch_o2 )
146         END DO
147      END DO
148
149      DO jj = 1, jpj
150         DO ji = 1, jpi
151            ! Compute CO2 flux for the sea and air
152#if ! defined key_cpl_carbon_cycle
153            zfld = atcco2 * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj)
154            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj)
155#else
156            zfld = atm_co2(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj)
157            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj)
158            ! compute flux of carbon
159            oce_co2(ji,jj) = ( zfld - zflu ) * rfact &
160               &             * e1t(ji,jj) * e2t(ji,jj) * tmask(ji,jj,1) * 1000.
161#endif
162            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1)
163
164            ! Compute O2 flux
165            zfld16 = atcox * chemc(ji,jj,2) * tmask(ji,jj,1) * zkgo2(ji,jj)
166            zflu16 = trn(ji,jj,1,jpoxy) * tmask(ji,jj,1) * zkgo2(ji,jj)
167            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + ( zfld16 - zflu16 ) / fse3t(ji,jj,1)
168
169#if defined key_diatrc 
170            ! Save diagnostics
171#  if ! defined key_iomput
172            trc2d(ji,jj,jp_pcs0_2d    ) = ( zfld - zflu )     * 1000. * tmask(ji,jj,1)
173            trc2d(ji,jj,jp_pcs0_2d + 1) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1)
174            trc2d(ji,jj,jp_pcs0_2d + 2) = zkgco2(ji,jj) * tmask(ji,jj,1)
175            trc2d(ji,jj,jp_pcs0_2d + 3) = ( atcco2 - zh2co3(ji,jj) / ( chemc(ji,jj,1) + rtrn ) ) &
176               &                            * tmask(ji,jj,1)
177#  else
178            zcflx(ji,jj) = ( zfld - zflu ) * 1000.  * tmask(ji,jj,1)
179            zoflx(ji,jj) = ( zfld16 - zflu16 ) * 1000. * tmask(ji,jj,1)
180            zkg  (ji,jj) = zkgco2(ji,jj) * tmask(ji,jj,1)
181            zdpco2(ji,jj) = ( atcco2 - zh2co3(ji,jj)      / ( chemc(ji,jj,1) + rtrn ) ) &
182              &             * tmask(ji,jj,1)
183            zdpo2 (ji,jj) = ( atcox  - trn(ji,jj,1,jpoxy) / ( chemc(ji,jj,2) + rtrn ) ) &
184              &             * tmask(ji,jj,1)
185#  endif
186#endif
187         END DO
188      END DO
189
190#if defined key_cpl_carbon_cycle
191      ! Total Flux of Carbon
192      DO jj = 1, jpj 
193        DO ji = 1, jpi
194           t_atm_co2_flx = t_atm_co2_flx + atm_co2(ji,jj) * tmask_i(ji,jj)
195           t_oce_co2_flx = t_oce_co2_flx + oce_co2(ji,jj) * tmask_i(ji,jj)
196        END DO
197      END DO
198
199      IF( MOD( kt, nspyr ) == 0 ) THEN
200        IF( lk_mpp ) THEN
201          CALL mpp_sum( t_atm_co2_flx )   ! sum over the global domain
202          CALL mpp_sum( t_oce_co2_flx )   ! sum over the global domain
203        ENDIF
204        ! Conversion in GtC/yr ; negative for outgoing from ocean
205        t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15
206        !
207        WRITE(numout,*) ' Atmospheric pCO2    :'
208        WRITE(numout,*) '-------------------- : ',kt,'  ',t_atm_co2_flx
209        WRITE(numout,*) '(ppm)'
210        WRITE(numout,*) 'Total Flux of Carbon out of the ocean :'
211        WRITE(numout,*) '-------------------- : ',t_oce_co2_flx
212        WRITE(numout,*) '(GtC/yr)'
213        t_atm_co2_flx = 0.
214        t_oce_co2_flx = 0.
215# if defined key_iomput
216        CALL iom_put( "tatpco2" , t_atm_co2_flx  )
217        CALL iom_put( "tco2flx" , t_oce_co2_flx  )
218#endif
219      ENDIF
220#endif
221
222      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
223         WRITE(charout, FMT="('flx ')")
224         CALL prt_ctl_trc_info(charout)
225         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
226      ENDIF
227
228# if defined key_diatrc && defined key_iomput
229      CALL iom_put( "Cflx" , zcflx  )
230      CALL iom_put( "Oflx" , zoflx  )
231      CALL iom_put( "Kg"   , zkg    )
232      CALL iom_put( "Dpco2", zdpco2 )
233      CALL iom_put( "Dpo2" , zdpo2  )
234#endif
235
236   END SUBROUTINE p4z_flx
237
238   SUBROUTINE p4z_flx_init
239
240      !!----------------------------------------------------------------------
241      !!                  ***  ROUTINE p4z_flx_init  ***
242      !!
243      !! ** Purpose :   Initialization of atmospheric conditions
244      !!
245      !! ** Method  :   Read the nampisext namelist and check the parameters
246      !!      called at the first timestep (nit000)
247      !! ** input   :   Namelist nampisext
248      !!
249      !!----------------------------------------------------------------------
250
251      NAMELIST/nampisext/ atcco2
252
253      REWIND( numnat )                     ! read numnat
254      READ  ( numnat, nampisext )
255
256      IF(lwp) THEN                         ! control print
257         WRITE(numout,*) ' '
258         WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext'
259         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
260         WRITE(numout,*) '    Atmospheric pCO2      atcco2      =', atcco2
261      ENDIF
262
263      ! number of time step per year 
264      nspyr = INT( nyear_len(1) * rday / rdt )
265
266#if defined key_cpl_carbon_cycle
267      ! Initialization of Flux of Carbon
268      oce_co2(:,:) = 0.
269      t_atm_co2_flx = 0.
270      t_oce_co2_flx = 0.
271#endif
272
273   END SUBROUTINE p4z_flx_init
274
275#else
276   !!======================================================================
277   !!  Dummy module :                                   No PISCES bio-model
278   !!======================================================================
279CONTAINS
280   SUBROUTINE p4z_flx( kt )                   ! Empty routine
281      INTEGER, INTENT( in ) ::   kt
282      WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt
283   END SUBROUTINE p4z_flx
284#endif 
285
286   !!======================================================================
287END MODULE  p4zflx
Note: See TracBrowser for help on using the repository browser.