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 NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z/p4zflx.F90 @ 10975

Last change on this file since 10975 was 10975, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Finish converting all TOP routines and knock-on effects of these conversions. Fully SETTE tested (SETTE tests 1-6 and 9). This completes the first stage conversion of TRA and TOP but need to revisit and pass ts and tr arrays through the argument lists where appropriate.

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