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/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90 @ 7607

Last change on this file since 7607 was 7607, checked in by cetlod, 7 years ago

v3.6 stable : add missing features for CMIP6 exercise, see ticket #1834

  • Property svn:keywords set to Id
File size: 18.4 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     !: pre-industrial atmospheric [co2] (ppm)   
41   LOGICAL           ::  ln_co2int  !: flag to read in a file and interpolate atmospheric pco2 or not
42   CHARACTER(len=34) ::  clname     !: filename of pco2 values
43   INTEGER           ::  nn_offset  !: 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  !: 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) ::  xconv  = 0.01_wp / 3600._wp !: coefficients for conversion
60
61   !!* Substitution
62#  include "top_substitute.h90"
63   !!----------------------------------------------------------------------
64   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
65   !! $Id$
66   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
67   !!----------------------------------------------------------------------
68CONTAINS
69
70   SUBROUTINE p4z_flx ( kt, knt )
71      !!---------------------------------------------------------------------
72      !!                     ***  ROUTINE p4z_flx  ***
73      !!
74      !! ** Purpose :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE
75      !!
76      !! ** Method  :
77      !!              - Include total atm P correction via Esbensen & Kushnir (1981)
78      !!              - Pressure correction NOT done for key_cpl_carbon_cycle
79      !!              - Remove Wanninkhof chemical enhancement;
80      !!              - Add option for time-interpolation of atcco2.txt 
81      !!---------------------------------------------------------------------
82      !
83      INTEGER, INTENT(in) ::   kt, knt   !
84      !
85      INTEGER  ::   ji, jj, jm, iind, iindm1
86      REAL(wp) ::   ztc, ztc2, ztc3, ztc4, zws, zkgwan
87      REAL(wp) ::   zfld, zflu, zfld16, zflu16, zfact
88      REAL(wp) ::   zvapsw, zsal, zfco2, zxc2, xCO2approx, ztkel, zfugcoeff
89      REAL(wp) ::   zph, zdic, zsch_o2, zsch_co2
90      REAL(wp) ::   zyr_dec, zdco2dt
91      CHARACTER (len=25) :: charout
92      REAL(wp), POINTER, DIMENSION(:,:) :: zkgco2, zkgo2, zh2co3, zoflx, zw2d, zpco2atm 
93      !!---------------------------------------------------------------------
94      !
95      IF( nn_timing == 1 )  CALL timing_start('p4z_flx')
96      !
97      CALL wrk_alloc( jpi, jpj, zkgco2, zkgo2, zh2co3, zoflx, zpco2atm )
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 .AND. knt == 1 ) 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 jj = 1, jpj
125         DO ji = 1, jpi
126            ! DUMMY VARIABLES FOR DIC, H+, AND BORATE
127            zfact = rhop(ji,jj,1) / 1000. + rtrn
128            zdic  = trb(ji,jj,1,jpdic)
129            zph   = MAX( hi(ji,jj,1), 1.e-10 ) / zfact
130            ! CALCULATE [H2CO3]
131            zh2co3(ji,jj) = zdic/(1. + ak13(ji,jj,1)/zph + ak13(ji,jj,1)*ak23(ji,jj,1)/zph**2)
132         END DO
133      END DO
134
135      ! --------------
136      ! COMPUTE FLUXES
137      ! --------------
138
139      ! FIRST COMPUTE GAS EXCHANGE COEFFICIENTS
140      ! -------------------------------------------
141
142!CDIR NOVERRCHK
143      DO jj = 1, jpj
144!CDIR NOVERRCHK
145         DO ji = 1, jpi
146            ztc  = MIN( 35., tsn(ji,jj,1,jp_tem) )
147            ztc2 = ztc * ztc
148            ztc3 = ztc * ztc2 
149            ztc4 = ztc2 * ztc2 
150            ! Compute the schmidt Number both O2 and CO2
151            zsch_co2 = 2116.8 - 136.25 * ztc + 4.7353 * ztc2 - 0.092307 * ztc3 + 0.0007555 * ztc4
152            zsch_o2  = 1920.4 - 135.6  * ztc + 5.2122 * ztc2 - 0.109390 * ztc3 + 0.0009377 * ztc4
153            !  wind speed
154            zws  = wndm(ji,jj) * wndm(ji,jj)
155            ! Compute the piston velocity for O2 and CO2
156            zkgwan = 0.251 * zws
157            zkgwan = zkgwan * xconv * ( 1.- fr_i(ji,jj) ) * tmask(ji,jj,1)
158# if defined key_degrad
159            zkgwan = zkgwan * facvol(ji,jj,1)
160#endif 
161            ! compute gas exchange for CO2 and O2
162            zkgco2(ji,jj) = zkgwan * SQRT( 660./ zsch_co2 )
163            zkgo2 (ji,jj) = zkgwan * SQRT( 660./ zsch_o2 )
164         END DO
165      END DO
166
167      DO jj = 1, jpj
168         DO ji = 1, jpi
169            ztkel  = tsn(ji,jj,1,jp_tem) + 273.15
170            zsal   = tsn(ji,jj,1,jp_sal) + ( 1.- tmask(ji,jj,1) ) * 35.
171            zvapsw = EXP(24.4543 - 67.4509*(100.0/ztkel) - 4.8489*LOG(ztkel/100) - 0.000544*zsal)
172            zpco2atm(ji,jj) = satmco2(ji,jj) * ( patm(ji,jj) - zvapsw )
173            zxc2 = (1.0 - zpco2atm(ji,jj) * 1E-6 )**2
174            zfugcoeff = EXP(patm(ji,jj) * (chemc(ji,jj,2) + 2.0 * zxc2 * chemc(ji,jj,3) )   &
175            &           / (82.05736 * ztkel))
176            zfco2 = zpco2atm(ji,jj) * zfugcoeff
177
178            ! Compute CO2 flux for the sea and air
179            zfld = zfco2 * chemc(ji,jj,1) * zkgco2(ji,jj)  ! (mol/L) * (m/s)
180            zflu = zh2co3(ji,jj) * zkgco2(ji,jj)                                   ! (mol/L) (m/s) ?
181            oce_co2(ji,jj) = ( zfld - zflu ) * rfact2 * e1e2t(ji,jj) * tmask(ji,jj,1) * 1000.
182            ! compute the trend
183            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) * rfact2 / fse3t(ji,jj,1) * tmask(ji,jj,1)
184
185            ! Compute O2 flux
186            zfld16 = patm(ji,jj) * chemo2(ji,jj,1) * zkgo2(ji,jj)          ! (mol/L) * (m/s)
187            zflu16 = trb(ji,jj,1,jpoxy) * zkgo2(ji,jj)
188            zoflx(ji,jj) = ( zfld16 - zflu16 ) * tmask(ji,jj,1)
189            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + zoflx(ji,jj) * rfact2 / fse3t(ji,jj,1)
190         END DO
191      END DO
192
193      t_oce_co2_flx     = glob_sum( oce_co2(:,:) )                    !  Total Flux of Carbon
194      t_oce_co2_flx_cum = t_oce_co2_flx_cum + t_oce_co2_flx       !  Cumulative Total Flux of Carbon
195!      t_atm_co2_flx     = glob_sum( satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2
196      t_atm_co2_flx     =  atcco2      ! Total atmospheric pCO2
197 
198      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
199         WRITE(charout, FMT="('flx ')")
200         CALL prt_ctl_trc_info(charout)
201         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
202      ENDIF
203
204      IF( lk_iomput .AND. knt == nrdttrc ) THEN
205         CALL wrk_alloc( jpi, jpj, zw2d ) 
206         IF( iom_use( "Cflx"  ) )  THEN
207            zw2d(:,:) = oce_co2(:,:) / e1e2t(:,:) * rfact2r
208            CALL iom_put( "Cflx"     , zw2d ) 
209         ENDIF
210         IF( iom_use( "Oflx"  ) )  THEN
211            zw2d(:,:) =  zoflx(:,:) * 1000 * tmask(:,:,1)
212            CALL iom_put( "Oflx" , zw2d )
213         ENDIF
214         IF( iom_use( "Kg"    ) )  THEN
215            zw2d(:,:) =  zkgco2(:,:) * tmask(:,:,1)
216            CALL iom_put( "Kg"   , zw2d )
217         ENDIF
218         IF( iom_use( "Dpco2" ) ) THEN
219           zw2d(:,:) = ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1)
220           CALL iom_put( "Dpco2" ,  zw2d )
221         ENDIF
222         IF( iom_use( "Dpo2" ) )  THEN
223           zw2d(:,:) = ( atcox * patm(:,:) - atcox * trn(:,:,1,jpoxy) / ( chemo2(:,:,1) + rtrn ) ) * tmask(:,:,1)
224           CALL iom_put( "Dpo2"  , zw2d )
225         ENDIF
226         IF( iom_use( "tcflx" ) )  CALL iom_put( "tcflx"    , t_oce_co2_flx * rfact2r )   ! molC/s
227         CALL iom_put( "tcflxcum" , t_oce_co2_flx_cum )      ! molC
228         !
229         CALL wrk_dealloc( jpi, jpj, zw2d )
230      ELSE
231         IF( ln_diatrc ) THEN
232            trc2d(:,:,jp_pcs0_2d    ) = oce_co2(:,:) / e1e2t(:,:) * rfact2r 
233            trc2d(:,:,jp_pcs0_2d + 1) = zoflx(:,:) * 1000 * tmask(:,:,1) 
234            trc2d(:,:,jp_pcs0_2d + 2) = zkgco2(:,:) * tmask(:,:,1) 
235            trc2d(:,:,jp_pcs0_2d + 3) = ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1)
236         ENDIF
237      ENDIF
238      !
239#if defined key_cpl_carbon_cycle
240      ! change units for carbon cycle coupling
241      oce_co2(:,:) = oce_co2(:,:) / e1e2t(:,:) * rfact2r ! in molC/m2/s
242#endif
243      !
244      CALL wrk_dealloc( jpi, jpj, zkgco2, zkgo2, zh2co3, zoflx, zpco2atm )
245      !
246      IF( nn_timing == 1 )  CALL timing_stop('p4z_flx')
247      !
248   END SUBROUTINE p4z_flx
249
250
251   SUBROUTINE p4z_flx_init
252      !!----------------------------------------------------------------------
253      !!                  ***  ROUTINE p4z_flx_init  ***
254      !!
255      !! ** Purpose :   Initialization of atmospheric conditions
256      !!
257      !! ** Method  :   Read the nampisext namelist and check the parameters
258      !!      called at the first timestep (nittrc000)
259      !! ** input   :   Namelist nampisext
260      !!----------------------------------------------------------------------
261      NAMELIST/nampisext/ln_co2int, atcco2, clname, nn_offset
262      INTEGER :: jm
263      INTEGER :: ios                 ! Local integer output status for namelist read
264      !!----------------------------------------------------------------------
265      !
266
267      REWIND( numnatp_ref )              ! Namelist nampisext in reference namelist : Pisces atm. conditions
268      READ  ( numnatp_ref, nampisext, IOSTAT = ios, ERR = 901)
269901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisext in reference namelist', lwp )
270
271      REWIND( numnatp_cfg )              ! Namelist nampisext in configuration namelist : Pisces atm. conditions
272      READ  ( numnatp_cfg, nampisext, IOSTAT = ios, ERR = 902 )
273902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisext in configuration namelist', lwp )
274      IF(lwm) WRITE ( numonp, nampisext )
275      !
276      IF(lwp) THEN                         ! control print
277         WRITE(numout,*) ' '
278         WRITE(numout,*) ' Namelist parameters for air-sea exchange, nampisext'
279         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
280         WRITE(numout,*) '    Choice for reading in the atm pCO2 file or constant value, ln_co2int =', ln_co2int
281         WRITE(numout,*) ' '
282      ENDIF
283      IF( .NOT.ln_co2int ) THEN
284         IF(lwp) THEN                         ! control print
285            WRITE(numout,*) '    Constant Atmospheric pCO2 value  atcco2    =', atcco2
286            WRITE(numout,*) ' '
287         ENDIF
288         satmco2(:,:)  = atcco2      ! Initialisation of atmospheric pco2
289      ELSE
290         IF(lwp)  THEN
291            WRITE(numout,*) '    Atmospheric pCO2 value  from file clname      =', TRIM( clname )
292            WRITE(numout,*) '    Offset model-data start year      nn_offset   =', nn_offset
293            WRITE(numout,*) ' '
294         ENDIF
295         CALL ctl_opn( numco2, TRIM( clname) , 'OLD', 'FORMATTED', 'SEQUENTIAL', -1 , numout, lwp )
296         jm = 0                      ! Count the number of record in co2 file
297         DO
298           READ(numco2,*,END=100) 
299           jm = jm + 1
300         END DO
301 100     nmaxrec = jm - 1 
302         ALLOCATE( years  (nmaxrec) )     ;      years  (:) = 0._wp
303         ALLOCATE( atcco2h(nmaxrec) )     ;      atcco2h(:) = 0._wp
304
305         REWIND(numco2)
306         DO jm = 1, nmaxrec          ! get  xCO2 data
307            READ(numco2, *)  years(jm), atcco2h(jm)
308            IF(lwp) WRITE(numout, '(f6.0,f7.2)')  years(jm), atcco2h(jm)
309         END DO
310         CLOSE(numco2)
311      ENDIF
312      !
313      oce_co2(:,:)  = 0._wp                ! Initialization of Flux of Carbon
314      t_oce_co2_flx = 0._wp
315      t_atm_co2_flx = 0._wp
316      !
317      CALL p4z_patm( nit000 )
318      !
319   END SUBROUTINE p4z_flx_init
320
321   SUBROUTINE p4z_patm( kt )
322
323      !!----------------------------------------------------------------------
324      !!                  ***  ROUTINE p4z_atm  ***
325      !!
326      !! ** Purpose :   Read and interpolate the external atmospheric sea-levl pressure
327      !! ** Method  :   Read the files and interpolate the appropriate variables
328      !!
329      !!----------------------------------------------------------------------
330      !! * arguments
331      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
332      !
333      INTEGER            ::  ierr
334      INTEGER            ::  ios      ! Local integer output status for namelist read
335      CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files
336      TYPE(FLD_N)        ::  sn_patm  ! informations about the fields to be read
337      !!
338      NAMELIST/nampisatm/ ln_presatm, sn_patm, cn_dir
339
340      !                                         ! ----------------------- !
341      IF( kt == nit000 ) THEN                   ! First call kt=nittrc000 !
342
343         REWIND( numnatp_ref )              ! Namelist nampisatm in reference namelist : Pisces atm. sea level pressure file
344         READ  ( numnatp_ref, nampisatm, IOSTAT = ios, ERR = 901)
345901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in reference namelist', lwp )
346
347         REWIND( numnatp_cfg )              ! Namelist nampisatm in configuration namelist : Pisces atm. sea level pressure file
348         READ  ( numnatp_cfg, nampisatm, IOSTAT = ios, ERR = 902 )
349902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in configuration namelist', lwp )
350         IF(lwm) WRITE ( numonp, nampisatm )
351         !
352         !
353         IF(lwp) THEN                                 !* control print
354            WRITE(numout,*)
355            WRITE(numout,*) '   Namelist nampisatm : Atmospheric Pressure as external forcing'
356            WRITE(numout,*) '      constant atmopsheric pressure (F) or from a file (T)  ln_presatm = ', ln_presatm
357            WRITE(numout,*)
358         ENDIF
359         !
360         IF( ln_presatm ) THEN
361            ALLOCATE( sf_patm(1), STAT=ierr )           !* allocate and fill sf_patm (forcing structure) with sn_patm
362            IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_flx: unable to allocate sf_patm structure' )
363            !
364            CALL fld_fill( sf_patm, (/ sn_patm /), cn_dir, 'p4z_flx', 'Atmospheric pressure ', 'nampisatm' )
365                                   ALLOCATE( sf_patm(1)%fnow(jpi,jpj,1)   )
366            IF( sn_patm%ln_tint )  ALLOCATE( sf_patm(1)%fdta(jpi,jpj,1,2) )
367         ENDIF
368         !                                         
369         IF( .NOT.ln_presatm )   patm(:,:) = 1.e0    ! Initialize patm if no reading from a file
370         !
371      ENDIF
372      !
373      IF( ln_presatm ) THEN
374         CALL fld_read( kt, 1, sf_patm )               !* input Patm provided at kt + 1/2
375         patm(:,:) = sf_patm(1)%fnow(:,:,1)                        ! atmospheric pressure
376      ENDIF
377      !
378   END SUBROUTINE p4z_patm
379
380   INTEGER FUNCTION p4z_flx_alloc()
381      !!----------------------------------------------------------------------
382      !!                     ***  ROUTINE p4z_flx_alloc  ***
383      !!----------------------------------------------------------------------
384      ALLOCATE( oce_co2(jpi,jpj), satmco2(jpi,jpj), patm(jpi,jpj), STAT=p4z_flx_alloc )
385      !
386      IF( p4z_flx_alloc /= 0 )   CALL ctl_warn('p4z_flx_alloc : failed to allocate arrays')
387      !
388   END FUNCTION p4z_flx_alloc
389
390#else
391   !!======================================================================
392   !!  Dummy module :                                   No PISCES bio-model
393   !!======================================================================
394CONTAINS
395   SUBROUTINE p4z_flx( kt )                   ! Empty routine
396      INTEGER, INTENT( in ) ::   kt
397      WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt
398   END SUBROUTINE p4z_flx
399#endif 
400
401   !!======================================================================
402END MODULE p4zflx
Note: See TracBrowser for help on using the repository browser.