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

source: branches/2011/dev_LOCEAN_2011/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zflx.F90 @ 3028

Last change on this file since 3028 was 3028, checked in by cetlod, 12 years ago

branch dev_LOCEAN_2011 : minor changes in TOP component relative to the management of additional diagnostics

  • Property svn:keywords set to Id
File size: 18.2 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   !!                  !  2011-02  (J. Simeon, J. Orr) Include total atm P correction
12   !!----------------------------------------------------------------------
13#if defined key_pisces
14   !!----------------------------------------------------------------------
15   !!   'key_pisces'                                       PISCES bio-model
16   !!----------------------------------------------------------------------
17   !!   p4z_flx       :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
18   !!   p4z_flx_init  :   Read the namelist
19   !!   p4z_patm      :   Read sfc atm pressure [atm] for each grid cell
20   !!----------------------------------------------------------------------
21   USE oce_trc                      !  shared variables between ocean and passive tracers
22   USE trc                          !  passive tracers common variables
23   USE sms_pisces                   !  PISCES Source Minus Sink variables
24   USE p4zche                       !  Chemical model
25   USE prtctl_trc                   !  print control for debugging
26   USE iom                          !  I/O manager
27   USE fldread                      !  read input fields
28#if defined key_cpl_carbon_cycle
29   USE sbc_oce, ONLY :  atm_co2     !  atmospheric pCO2               
30#endif
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   p4z_flx 
36   PUBLIC   p4z_flx_init 
37   PUBLIC   p4z_flx_alloc 
38
39   !                                      !!** Namelist  nampisext  **
40   REAL(wp)          ::  atcco2    = 278._wp       !: pre-industrial atmospheric [co2] (ppm)   
41   LOGICAL           ::  ln_co2int = .FALSE.       !: flag to read in a file and interpolate atmospheric pco2 or not
42   CHARACTER(len=34) ::  clname    = 'atcco2.txt'  !: filename of pco2 values
43   INTEGER           ::  nn_offset = 0             !: Offset model-data start year (default = 0)
44
45   !!  Variables related to reading atmospheric CO2 time history   
46   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) :: atcco2h, years
47   INTEGER  :: nmaxrec, numco2
48
49   !                                         !!* nampisatm namelist (Atmospheric PRessure) *
50   LOGICAL, PUBLIC ::   ln_presatm = .true.  !: ref. pressure: global mean Patm (F) or a constant (F)
51
52   REAL(wp) , ALLOCATABLE, SAVE, DIMENSION(:,:)  ::  patm      ! atmospheric pressure at kt                 [N/m2]
53   TYPE(FLD), ALLOCATABLE,       DIMENSION(:)    ::  sf_patm   ! structure of input fields (file informations, fields read)
54
55
56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: oce_co2   !: ocean carbon flux
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: satmco2   !: atmospheric pco2
58
59   REAL(wp) ::  t_oce_co2_flx               !: Total ocean carbon flux
60   REAL(wp) ::  t_atm_co2_flx               !: global mean of atmospheric pco2
61   REAL(wp) ::  area                        !: ocean surface
62   REAL(wp) ::  xconv  = 0.01_wp / 3600._wp !: coefficients for conversion
63
64   !!* Substitution
65#  include "top_substitute.h90"
66   !!----------------------------------------------------------------------
67   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
68   !! $Id$
69   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
70   !!----------------------------------------------------------------------
71CONTAINS
72
73   SUBROUTINE p4z_flx ( kt )
74      !!---------------------------------------------------------------------
75      !!                     ***  ROUTINE p4z_flx  ***
76      !!
77      !! ** Purpose :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
78      !!
79      !! ** Method  :
80      !!              - Include total atm P correction via Esbensen & Kushnir (1981)
81      !!              - Pressure correction NOT done for key_cpl_carbon_cycle
82      !!              - Remove Wanninkhof chemical enhancement;
83      !!              - Add option for time-interpolation of atcco2.txt 
84      !!---------------------------------------------------------------------
85      USE wrk_nemo, ONLY:  wrk_in_use, wrk_not_released
86      USE wrk_nemo, ONLY:  zkgco2 => wrk_2d_11 , zkgo2 => wrk_2d_12 
87      USE wrk_nemo, ONLY:  zh2co3 => wrk_2d_13 , zoflx => wrk_2d_14 
88      USE wrk_nemo, ONLY:   
89      !
90      INTEGER, INTENT(in) ::   kt   !
91      !
92      INTEGER  ::   ji, jj, jm, iind, iindm1
93      REAL(wp) ::   ztc, ztc2, ztc3, zws, zkgwan
94      REAL(wp) ::   zfld, zflu, zfld16, zflu16, zfact
95      REAL(wp) ::   zph, zah2, zbot, zdic, zalk, zsch_o2, zalka, zsch_co2
96      REAL(wp) ::   zyr_dec, zdco2dt
97      CHARACTER (len=25) :: charout
98      !!---------------------------------------------------------------------
99
100      IF( wrk_in_use(2, 11,12,13,14) ) THEN
101         CALL ctl_stop('p4z_flx: requested workspace arrays unavailable')   ;   RETURN
102      ENDIF
103
104      ! SURFACE CHEMISTRY (PCO2 AND [H+] IN
105      !     SURFACE LAYER); THE RESULT OF THIS CALCULATION
106      !     IS USED TO COMPUTE AIR-SEA FLUX OF CO2
107
108      CALL p4z_patm( kt )    ! Get sea-level pressure (E&K [1981] climatology) for use in flux calcs
109
110      IF( ln_co2int ) THEN 
111         ! Linear temporal interpolation  of atmospheric pco2.  atcco2.txt has annual values.
112         ! Caveats: First column of .txt must be in years, decimal  years preferably.
113         ! For nn_offset, if your model year is iyy, nn_offset=(years(1)-iyy)
114         ! then the first atmospheric CO2 record read is at years(1)
115         zyr_dec = REAL( nyear + nn_offset, wp ) + REAL( nday_year, wp ) / REAL( nyear_len(1), wp )
116         jm = 2
117         DO WHILE( jm <= nmaxrec .AND. years(jm-1) < zyr_dec .AND. years(jm) >= zyr_dec ) ;  jm = jm + 1 ;  END DO
118         iind = jm  ;   iindm1 = jm - 1
119         zdco2dt = ( atcco2h(iind) - atcco2h(iindm1) ) / ( years(iind) - years(iindm1) + rtrn )
120         atcco2  = zdco2dt * ( zyr_dec - years(iindm1) ) + atcco2h(iindm1)
121         satmco2(:,:) = atcco2 
122      ENDIF
123
124#if defined key_cpl_carbon_cycle
125      satmco2(:,:) = atm_co2(:,:)
126#endif
127
128      DO jm = 1, 10
129!CDIR NOVERRCHK
130         DO jj = 1, jpj
131!CDIR NOVERRCHK
132            DO ji = 1, jpi
133
134               ! DUMMY VARIABLES FOR DIC, H+, AND BORATE
135               zbot  = borat(ji,jj,1)
136               zfact = rhop(ji,jj,1) / 1000. + rtrn
137               zdic  = trn(ji,jj,1,jpdic) / zfact
138               zph   = MAX( hi(ji,jj,1), 1.e-10 ) / zfact
139               zalka = trn(ji,jj,1,jptal) / zfact
140
141               ! CALCULATE [ALK]([CO3--], [HCO3-])
142               zalk  = zalka - (  akw3(ji,jj,1) / zph - zph + zbot / ( 1.+ zph / akb3(ji,jj,1) )  )
143
144               ! CALCULATE [H+] AND [H2CO3]
145               zah2   = SQRT(  (zdic-zalk)**2 + 4.* ( zalk * ak23(ji,jj,1)   &
146                  &                                        / ak13(ji,jj,1) ) * ( 2.* zdic - zalk )  )
147               zah2   = 0.5 * ak13(ji,jj,1) / zalk * ( ( zdic - zalk ) + zah2 )
148               zh2co3(ji,jj) = ( 2.* zdic - zalk ) / ( 2.+ ak13(ji,jj,1) / zah2 ) * zfact
149               hi(ji,jj,1)   = zah2 * zfact
150            END DO
151         END DO
152      END DO
153
154
155      ! --------------
156      ! COMPUTE FLUXES
157      ! --------------
158
159      ! FIRST COMPUTE GAS EXCHANGE COEFFICIENTS
160      ! -------------------------------------------
161
162!CDIR NOVERRCHK
163      DO jj = 1, jpj
164!CDIR NOVERRCHK
165         DO ji = 1, jpi
166            ztc  = MIN( 35., tsn(ji,jj,1,jp_tem) )
167            ztc2 = ztc * ztc
168            ztc3 = ztc * ztc2 
169            ! Compute the schmidt Number both O2 and CO2
170            zsch_co2 = 2073.1 - 125.62 * ztc + 3.6276 * ztc2 - 0.043126 * ztc3
171            zsch_o2  = 1953.4 - 128.0  * ztc + 3.9918 * ztc2 - 0.050091 * ztc3
172            !  wind speed
173            zws  = wndm(ji,jj) * wndm(ji,jj)
174            ! Compute the piston velocity for O2 and CO2
175            zkgwan = 0.3 * zws  + 2.5 * ( 0.5246 + 0.016256 * ztc + 0.00049946  * ztc2 )
176            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1)
177# if defined key_degrad
178            zkgwan = zkgwan * facvol(ji,jj,1)
179#endif 
180            ! compute gas exchange for CO2 and O2
181            zkgco2(ji,jj) = zkgwan * SQRT( 660./ zsch_co2 )
182            zkgo2 (ji,jj) = zkgwan * SQRT( 660./ zsch_o2 )
183         END DO
184      END DO
185
186      DO jj = 1, jpj
187         DO ji = 1, jpi
188            ! Compute CO2 flux for the sea and air
189            zfld = satmco2(ji,jj) * patm(ji,jj) * tmask(ji,jj,1) * chemc(ji,jj,1) * zkgco2(ji,jj)   ! (mol/L) * (m/s)
190            zflu = zh2co3(ji,jj) * tmask(ji,jj,1) * zkgco2(ji,jj)                                   ! (mol/L) (m/s) ?
191            oce_co2(ji,jj) = ( zfld - zflu ) * rfact * e1e2t(ji,jj) * tmask(ji,jj,1) * 1000.
192            ! compute the trend
193            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) / fse3t(ji,jj,1)
194
195            ! Compute O2 flux
196            zfld16 = atcox * patm(ji,jj) * chemc(ji,jj,2) * tmask(ji,jj,1) * zkgo2(ji,jj)          ! (mol/L) * (m/s)
197            zflu16 = trn(ji,jj,1,jpoxy) * tmask(ji,jj,1) * zkgo2(ji,jj)
198            zoflx(ji,jj) = zfld16 - zflu16
199            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + zoflx(ji,jj) / fse3t(ji,jj,1)
200         END DO
201      END DO
202
203      t_oce_co2_flx = t_oce_co2_flx + glob_sum( oce_co2(:,:) )            ! Cumulative Total Flux of Carbon
204      IF( kt == nitend ) THEN
205         t_atm_co2_flx = glob_sum( satmco2(:,:) * patm(:,:) * e1e2t(:,:) )            ! Total atmospheric pCO2
206         !
207         t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15             ! Conversion in PgC ; negative for out of the ocean
208         t_atm_co2_flx = t_atm_co2_flx  / area                            ! global mean of atmospheric pCO2
209         !
210         IF( lwp) THEN
211            WRITE(numout,*)
212            WRITE(numout,*) ' Global mean of atmospheric pCO2 (ppm) at it= ', kt, ' date= ', ndastp
213            WRITE(numout,*) '------------------------------------------------------- :  ',t_atm_co2_flx
214            WRITE(numout,*)
215            WRITE(numout,*) ' Cumulative total Flux of Carbon out of the ocean (PgC) :'
216            WRITE(numout,*) '-------------------------------------------------------  ',t_oce_co2_flx
217         ENDIF
218         !
219      ENDIF
220
221      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
222         WRITE(charout, FMT="('flx ')")
223         CALL prt_ctl_trc_info(charout)
224         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
225      ENDIF
226
227      IF( ln_diatrc ) THEN
228         IF( lk_iomput ) THEN
229            CALL iom_put( "Cflx" , oce_co2(:,:) / e1e2t(:,:) / rfact ) 
230            CALL iom_put( "Oflx" , zoflx(:,:) * 1000 * tmask(:,:,1)  )
231            CALL iom_put( "Kg"   , zkgco2(:,:) * tmask(:,:,1) )
232            CALL iom_put( "Dpco2", ( satmco2(:,:) * patm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) )
233            CALL iom_put( "Dpo2" , ( atcox * patm(:,:) - trn(:,:,1,jpoxy) / ( chemc(:,:,2) + rtrn ) ) * tmask(:,:,1) )
234         ELSE
235            trc2d(:,:,jp_pcs0_2d    ) = oce_co2(:,:) / e1e2t(:,:) / rfact 
236            trc2d(:,:,jp_pcs0_2d + 1) = zoflx(:,:) * 1000 * tmask(:,:,1) 
237            trc2d(:,:,jp_pcs0_2d + 2) = zkgco2(:,:) * tmask(:,:,1) 
238            trc2d(:,:,jp_pcs0_2d + 3) = ( satmco2(:,:) * patm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) 
239         ENDIF
240      ENDIF
241      !
242      IF( wrk_not_released(2, 11,12,13,14) ) CALL ctl_stop('p4z_flx: failed to release workspace arrays')
243      !
244   END SUBROUTINE p4z_flx
245
246
247   SUBROUTINE p4z_flx_init
248      !!----------------------------------------------------------------------
249      !!                  ***  ROUTINE p4z_flx_init  ***
250      !!
251      !! ** Purpose :   Initialization of atmospheric conditions
252      !!
253      !! ** Method  :   Read the nampisext namelist and check the parameters
254      !!      called at the first timestep (nit000)
255      !! ** input   :   Namelist nampisext
256      !!----------------------------------------------------------------------
257      NAMELIST/nampisext/ln_co2int, atcco2, clname, nn_offset
258      INTEGER :: jm
259      !!----------------------------------------------------------------------
260      !
261      REWIND( numnatp )                     ! read numnatp
262      READ  ( numnatp, nampisext )
263      !
264      IF(lwp) THEN                         ! control print
265         WRITE(numout,*) ' '
266         WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext'
267         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
268         WRITE(numout,*) '    Choice for reading in the atm pCO2 file or constant value, ln_co2int =', ln_co2int
269         WRITE(numout,*) ' '
270      ENDIF
271      IF( .NOT.ln_co2int ) THEN
272         IF(lwp) THEN                         ! control print
273            WRITE(numout,*) '    Constant Atmospheric pCO2 value  atcco2    =', atcco2
274            WRITE(numout,*) ' '
275         ENDIF
276         satmco2(:,:)  = atcco2      ! Initialisation of atmospheric pco2
277      ELSE
278         IF(lwp)  THEN
279            WRITE(numout,*) '    Atmospheric pCO2 value  from file clname      =', TRIM( clname )
280            WRITE(numout,*) '    Offset model-data start year      nn_offset   =', nn_offset
281            WRITE(numout,*) ' '
282         ENDIF
283         CALL ctl_opn( numco2, TRIM( clname) , 'OLD', 'FORMATTED', 'SEQUENTIAL', -1 , numout, lwp )
284         jm = 0                      ! Count the number of record in co2 file
285         DO
286           READ(numco2,*,END=100) 
287           jm = jm + 1
288         END DO
289 100     nmaxrec = jm - 1 
290         ALLOCATE( years  (nmaxrec) )     ;      years  (:) = 0._wp
291         ALLOCATE( atcco2h(nmaxrec) )     ;      atcco2h(:) = 0._wp
292
293         REWIND(numco2)
294         DO jm = 1, nmaxrec          ! get  xCO2 data
295            READ(numco2, *)  years(jm), atcco2h(jm)
296            IF(lwp) WRITE(numout, '(f6.0,f7.2)')  years(jm), atcco2h(jm)
297         END DO
298         CLOSE(numco2)
299      ENDIF
300      !
301      area = glob_sum( e1e2t(:,:) )        ! interior global domain surface
302      !
303      oce_co2(:,:)  = 0._wp                ! Initialization of Flux of Carbon
304      t_atm_co2_flx = 0._wp
305      t_oce_co2_flx = 0._wp
306      !
307   END SUBROUTINE p4z_flx_init
308
309   SUBROUTINE p4z_patm( kt )
310
311      !!----------------------------------------------------------------------
312      !!                  ***  ROUTINE p4z_atm  ***
313      !!
314      !! ** Purpose :   Read and interpolate the external atmospheric sea-levl pressure
315      !! ** Method  :   Read the files and interpolate the appropriate variables
316      !!
317      !!----------------------------------------------------------------------
318      !! * arguments
319      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
320      !
321      INTEGER            ::  ierr
322      CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files
323      TYPE(FLD_N)        ::  sn_patm  ! informations about the fields to be read
324      !!
325      NAMELIST/nampisatm/ ln_presatm, sn_patm, cn_dir
326
327      !                                         ! -------------------- !
328      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
329         !                                      ! -------------------- !
330         !                                            !* set file information (default values)
331         ! ... default values (NB: frequency positive => hours, negative => months)
332         !            !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
333         !            !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
334         sn_patm = FLD_N( 'pres'  ,    24     ,  'patm'    ,  .false.   , .true.  ,   'yearly'  , ''       , ''       )
335         cn_dir  = './'          ! directory in which the Patm data are
336
337         REWIND( numnatp )                             !* read in namlist nampisatm
338         READ  ( numnatp, nampisatm ) 
339         !
340         !
341         IF(lwp) THEN                                 !* control print
342            WRITE(numout,*)
343            WRITE(numout,*) '   Namelist nampisatm : Atmospheric Pressure as external forcing'
344            WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm = ', ln_presatm
345            WRITE(numout,*)
346         ENDIF
347         !
348         IF( ln_presatm ) THEN
349            ALLOCATE( sf_patm(1), STAT=ierr )           !* allocate and fill sf_patm (forcing structure) with sn_patm
350            IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_flx: unable to allocate sf_patm structure' )
351            !
352            CALL fld_fill( sf_patm, (/ sn_patm /), cn_dir, 'p4z_flx', 'Atmospheric pressure ', 'nampisatm' )
353                                   ALLOCATE( sf_patm(1)%fnow(jpi,jpj,1)   )
354            IF( sn_patm%ln_tint )  ALLOCATE( sf_patm(1)%fdta(jpi,jpj,1,2) )
355         ENDIF
356         !                                         
357         IF( .NOT.ln_presatm )   patm(:,:) = 1.e0    ! Initialize patm if no reading from a file
358         !
359      ENDIF
360      !
361      IF( ln_presatm ) THEN
362         CALL fld_read( kt, 1, sf_patm )               !* input Patm provided at kt + 1/2
363         patm(:,:) = sf_patm(1)%fnow(:,:,1)                        ! atmospheric pressure
364      ENDIF
365      !
366   END SUBROUTINE p4z_patm
367
368   INTEGER FUNCTION p4z_flx_alloc()
369      !!----------------------------------------------------------------------
370      !!                     ***  ROUTINE p4z_flx_alloc  ***
371      !!----------------------------------------------------------------------
372      ALLOCATE( oce_co2(jpi,jpj), satmco2(jpi,jpj), patm(jpi,jpj), STAT=p4z_flx_alloc )
373      !
374      IF( p4z_flx_alloc /= 0 )   CALL ctl_warn('p4z_flx_alloc : failed to allocate arrays')
375      !
376   END FUNCTION p4z_flx_alloc
377
378#else
379   !!======================================================================
380   !!  Dummy module :                                   No PISCES bio-model
381   !!======================================================================
382CONTAINS
383   SUBROUTINE p4z_flx( kt )                   ! Empty routine
384      INTEGER, INTENT( in ) ::   kt
385      WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt
386   END SUBROUTINE p4z_flx
387#endif 
388
389   !!======================================================================
390END MODULE  p4zflx
Note: See TracBrowser for help on using the repository browser.