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/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90 @ 5288

Last change on this file since 5288 was 5288, checked in by aumont, 9 years ago

various bug fixes and updates of PISCES quota

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