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.
p4zopt.F90 in NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/P4Z/p4zopt.F90 @ 14416

Last change on this file since 14416 was 14416, checked in by cetlod, 4 years ago

dev_r14383_PISCES_NEWDEV_PISCO : minor improvments

  • Property svn:keywords set to Id
File size: 20.8 KB
Line 
1MODULE p4zopt
2   !!======================================================================
3   !!                         ***  MODULE p4zopt  ***
4   !! TOP - PISCES : Compute the light availability in the water column
5   !!======================================================================
6   !! History :  1.0  !  2004     (O. Aumont) Original code
7   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!            3.2  !  2009-04  (C. Ethe, G. Madec)  optimisation
9   !!            3.4  !  2011-06  (O. Aumont, C. Ethe) Improve light availability of nano & diat
10   !!----------------------------------------------------------------------
11   !!   p4z_opt       : light availability in the water column
12   !!----------------------------------------------------------------------
13   USE trc            ! tracer variables
14   USE oce_trc        ! tracer-ocean share variables
15   USE sms_pisces     ! Source Minus Sink of PISCES
16   USE iom            ! I/O manager
17   USE fldread        !  time interpolation
18   USE prtctl         !  print control for debugging
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   p4z_opt        ! called in p4zbio.F90 module
24   PUBLIC   p4z_opt_init   ! called in trcsms_pisces.F90 module
25   PUBLIC   p4z_opt_alloc
26
27   !! * Shared module variables
28
29   LOGICAL  ::   ln_varpar   ! boolean for variable PAR fraction
30   REAL(wp) ::   parlux      ! Fraction of shortwave as PAR
31   REAL(wp) ::   xparsw      ! parlux/3
32   REAL(wp) ::   xsi0r       ! 1. /rn_si0
33
34   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_par      ! structure of input par
35   INTEGER , PARAMETER :: nbtimes = 366  !: maximum number of times record in a file
36   INTEGER  :: ntimes_par                ! number of time steps in a file
37   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   par_varsw      ! PAR fraction of shortwave
38   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ekb, ekg, ekr  ! wavelength (Red-Green-Blue)
39   
40   !! * Substitutions
41#  include "do_loop_substitute.h90"
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
45   !! $Id$
46   !! Software governed by the CeCILL license (see ./LICENSE)
47   !!----------------------------------------------------------------------
48CONTAINS
49
50   SUBROUTINE p4z_opt( kt, knt, Kbb, Kmm )
51      !!---------------------------------------------------------------------
52      !!                     ***  ROUTINE p4z_opt  ***
53      !!
54      !! ** Purpose :   Compute the light availability in the water column
55      !!              depending on the depth and the chlorophyll concentration
56      !!
57      !! ** Method  : - ???
58      !!---------------------------------------------------------------------
59      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step
60      INTEGER, INTENT(in) ::   Kbb, Kmm  ! time level indices
61      !
62      INTEGER  ::   ji, jj, jk
63      INTEGER  ::   irgb
64      REAL(wp) ::   zchl
65      REAL(wp) ::   zc0 , zc1 , zc2, zc3, z1_dep
66      REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zetmp5
67      REAL(wp), DIMENSION(jpi,jpj    ) :: zdepmoy, zetmp1, zetmp2, zetmp3, zetmp4
68      REAL(wp), DIMENSION(jpi,jpj    ) :: zqsr100, zqsr_corr
69      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zpar, ze0, ze1, ze2, ze3
70      !!---------------------------------------------------------------------
71      !
72      IF( ln_timing )   CALL timing_start('p4z_opt')
73
74      IF( knt == 1 .AND. ln_varpar )   CALL p4z_opt_sbc( kt )
75
76      !     Initialisation of variables used to compute PAR
77      !     -----------------------------------------------
78      ze1(:,:,:) = 0._wp
79      ze2(:,:,:) = 0._wp
80      ze3(:,:,:) = 0._wp
81
82      !
83      ! Attenuation coef. function of Chlorophyll and wavelength (Red-Green-Blue)
84      ! Thus the light penetration scheme is based on a decomposition of PAR
85      ! into three wave length domains. This was first officially published
86      ! in Lengaigne et al. (2007).
87      ! --------------------------------------------------------
88      !
89      ! Computation of the light attenuation parameters based on a
90      ! look-up table
91      DO_3D( 1, 1, 1, 1, 1, jpkm1 )
92         zchl =  ( tr(ji,jj,jk,jpnch,Kbb) + tr(ji,jj,jk,jpdch,Kbb) + rtrn ) * 1.e6
93         IF( ln_p5z )   zchl = zchl + tr(ji,jj,jk,jppch,Kbb) * 1.e6
94         zchl = MIN(  10. , MAX( 0.05, zchl )  )
95         irgb = NINT( 41 + 20.* LOG10( zchl ) + rtrn )
96         !                                                         
97         ekb(ji,jj,jk) = rkrgb(1,irgb) * e3t(ji,jj,jk,Kmm)
98         ekg(ji,jj,jk) = rkrgb(2,irgb) * e3t(ji,jj,jk,Kmm)
99         ekr(ji,jj,jk) = rkrgb(3,irgb) * e3t(ji,jj,jk,Kmm)
100      END_3D
101
102
103      ! Photosynthetically Available Radiation (PAR)
104      ! Two cases are considered in the following :
105      ! (1) An explicit diunal cycle is activated. In that case, mean
106      ! QSR is used as PISCES in its current state has not been parameterized
107      ! for an explicit diurnal cycle
108      ! (2) no diurnal cycle of SW is active and in that case, QSR is used.
109      ! --------------------------------------------
110      IF( l_trcdm2dc ) THEN                     !  diurnal cycle
111         !
112          !
113         ! SW over the ice free zone of the grid cell. This assumes that
114         ! SW is zero below sea ice which is a very crude assumption that is
115         ! not fully correct with LIM3 and SI3 but no information is
116         ! currently available to do a better job. SHould be improved in the
117         ! (near) future.
118         zqsr_corr(:,:) = qsr_mean(:,:) / ( 1.-fr_i(:,:) + rtrn )
119         !
120         CALL p4z_opt_par( kt, Kmm, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100 ) 
121         !
122         ! Used PAR is computed for each phytoplankton species
123         ! etot_ndcy is PAR at level jk averaged over 24h.
124         ! Due to their size, they have different light absorption characteristics
125         DO jk = 1, nksr     
126            etot_ndcy(:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk)
127            enano    (:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk)
128            ediat    (:,:,jk) =  1.62 * ze1(:,:,jk) + 0.74 * ze2(:,:,jk) + 0.63 * ze3(:,:,jk)
129         END DO
130         IF( ln_p5z ) THEN
131            DO jk = 1, nksr     
132              epico  (:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk)
133            END DO
134         ENDIF
135         !
136         ! SW over the ice free zone of the grid cell. This assumes that
137         ! SW is zero below sea ice which is a very crude assumption that is
138         ! not fully correct with LIM3 and SI3 but no information is
139         ! currently available to do a better job. SHould be improved in the
140         ! (near) future.
141
142         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn )
143         !
144         CALL p4z_opt_par( kt, Kmm, zqsr_corr, ze1, ze2, ze3 ) 
145         !
146         ! Total PAR computation at level jk that includes the diurnal cycle
147         DO jk = 1, nksr     
148            etot(:,:,jk) =  ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk)
149         END DO
150         !
151      ELSE   ! no diurnal cycle
152         !
153         !
154         ! SW over the ice free zone of the grid cell. This assumes that
155         ! SW is zero below sea ice which is a very crude assumption that is
156         ! not fully correct with LIM3 and SI3 but no information is
157         ! currently available to do a better job. SHould be improved in the
158         ! (near) future.
159         zqsr_corr(:,:) = qsr(:,:) / ( 1.-fr_i(:,:) + rtrn )
160         !
161         CALL p4z_opt_par( kt, Kmm, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100  ) 
162         !
163
164         ! Used PAR is computed for each phytoplankton species
165         ! Due to their size, they have different light absorption characteristics
166         DO jk = 1, nksr     
167            etot (:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk)    ! Total PAR
168            enano(:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk)  ! Nanophytoplankton
169            ediat(:,:,jk) =  1.62 * ze1(:,:,jk) + 0.74 * ze2(:,:,jk) + 0.63 * ze3(:,:,jk)  ! Diatoms
170         END DO
171         IF( ln_p5z ) THEN
172            DO jk = 1, nksr     
173              epico(:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk)  ! Picophytoplankton (PISCES-QUOTA)
174            END DO
175         ENDIF
176         etot_ndcy(:,:,:) =  etot(:,:,:) 
177      ENDIF
178
179
180      ! Biophysical feedback part (computation of vertical penetration of SW)
181      IF( ln_qsr_bio ) THEN                    !* heat flux accros w-level (used in the dynamics)
182         !                                     !  ------------------------
183         CALL p4z_opt_par( kt, Kmm, qsr, ze1, ze2, ze3, pe0=ze0 )
184         !
185         etot3(:,:,1) =  qsr(:,:) * tmask(:,:,1)
186         DO jk = 2, nksr + 1
187            etot3(:,:,jk) =  ( ze0(:,:,jk) + ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk) ) * tmask(:,:,jk)
188         END DO
189         !                                     !  ------------------------
190      ENDIF
191     
192      ! Euphotic depth and level
193      ! Two definitions of the euphotic zone are used here.
194      ! (1) The classical definition based on the relative threshold value
195      ! (2) An alternative definition based on a absolute threshold value.
196      ! -------------------------------------------------------------------
197      neln(:,:) = 1
198      heup   (:,:) = gdepw(:,:,2,Kmm)
199      heup_01(:,:) = gdepw(:,:,2,Kmm)
200
201      DO_3D( 1, 1, 1, 1, 2, nksr )
202        IF( etot_ndcy(ji,jj,jk) * tmask(ji,jj,jk) >=  zqsr100(ji,jj) )  THEN
203           neln(ji,jj) = jk+1                    ! Euphotic level : 1rst T-level strictly below Euphotic layer
204           !                                     ! nb: ensure the compatibility with nmld_trc definition in trd_mld_trc_zint
205           heup(ji,jj) = gdepw(ji,jj,jk+1,Kmm)     ! Euphotic layer depth
206        ENDIF
207        IF( etot_ndcy(ji,jj,jk) * tmask(ji,jj,jk) >= 0.10 )  THEN
208           heup_01(ji,jj) = gdepw(ji,jj,jk+1,Kmm)  ! Euphotic layer depth (light level definition)
209        ENDIF
210      END_3D
211      !
212      ! The euphotic depth can not exceed 300 meters.
213      heup   (:,:) = MIN( 300., heup   (:,:) )
214      heup_01(:,:) = MIN( 300., heup_01(:,:) )
215     
216      ! Mean PAR over the mixed layer
217      ! -----------------------------
218      zdepmoy(:,:)   = 0.e0             
219      zetmp1 (:,:)   = 0.e0
220      zetmp2 (:,:)   = 0.e0
221
222      DO_3D( 1, 1, 1, 1, 1, nksr )
223         IF( gdepw(ji,jj,jk+1,Kmm) <= hmld(ji,jj) ) THEN
224            zetmp1 (ji,jj) = zetmp1 (ji,jj) + etot     (ji,jj,jk) * e3t(ji,jj,jk,Kmm) ! Actual PAR for remineralisation
225            zetmp2 (ji,jj) = zetmp2 (ji,jj) + etot_ndcy(ji,jj,jk) * e3t(ji,jj,jk,Kmm) ! Par averaged over 24h for production
226            zdepmoy(ji,jj) = zdepmoy(ji,jj) +                       e3t(ji,jj,jk,Kmm)
227         ENDIF
228      END_3D
229      !
230      emoy(:,:,:) = etot(:,:,:)       ! remineralisation
231      zpar(:,:,:) = etot_ndcy(:,:,:)  ! diagnostic : PAR with no diurnal cycle
232      !
233      DO_3D( 1, 1, 1, 1, 1, nksr )
234         IF( gdepw(ji,jj,jk+1,Kmm) <= hmld(ji,jj) ) THEN
235            z1_dep = 1. / ( zdepmoy(ji,jj) + rtrn )
236            emoy (ji,jj,jk) = zetmp1(ji,jj) * z1_dep
237            zpar (ji,jj,jk) = zetmp2(ji,jj) * z1_dep
238         ENDIF
239      END_3D
240
241      ! Computation of the mean usable light for the different phytoplankton
242      ! groups based on their absorption characteristics.
243      zdepmoy(:,:)   = 0.e0
244      zetmp3 (:,:)   = 0.e0
245      zetmp4 (:,:)   = 0.e0
246      !
247      DO_3D( 1, 1, 1, 1, 1, nksr )
248         IF( gdepw(ji,jj,jk+1,Kmm) <= MIN(hmld(ji,jj), heup_01(ji,jj)) ) THEN
249            zetmp3 (ji,jj) = zetmp3 (ji,jj) + enano    (ji,jj,jk) * e3t(ji,jj,jk,Kmm) ! Nanophytoplankton
250            zetmp4 (ji,jj) = zetmp4 (ji,jj) + ediat    (ji,jj,jk) * e3t(ji,jj,jk,Kmm) ! Diatoms
251            zdepmoy(ji,jj) = zdepmoy(ji,jj) +                       e3t(ji,jj,jk,Kmm)
252         ENDIF
253      END_3D
254      enanom(:,:,:) = enano(:,:,:)
255      ediatm(:,:,:) = ediat(:,:,:)
256      !
257      DO_3D( 1, 1, 1, 1, 1, nksr )
258         IF( gdepw(ji,jj,jk+1,Kmm) <= hmld(ji,jj) ) THEN
259            z1_dep = 1. / ( zdepmoy(ji,jj) + rtrn )
260            enanom(ji,jj,jk) = zetmp3(ji,jj) * z1_dep
261            ediatm(ji,jj,jk) = zetmp4(ji,jj) * z1_dep
262         ENDIF
263      END_3D
264      !
265      IF( ln_p5z ) THEN
266         ! Picophytoplankton when using PISCES-QUOTA
267         ALLOCATE( zetmp5(jpi,jpj) )  ;   zetmp5 (:,:) = 0.e0
268         DO_3D( 1, 1, 1, 1, 1, nksr )
269            IF( gdepw(ji,jj,jk+1,Kmm) <= MIN(hmld(ji,jj), heup_01(ji,jj)) ) THEN
270               zetmp5(ji,jj)  = zetmp5 (ji,jj) + epico(ji,jj,jk) * e3t(ji,jj,jk,Kmm)
271            ENDIF
272         END_3D
273         !
274         epicom(:,:,:) = epico(:,:,:)
275         !
276         DO_3D( 1, 1, 1, 1, 1, nksr )
277            IF( gdepw(ji,jj,jk+1,Kmm) <= hmld(ji,jj) ) THEN
278               z1_dep = 1. / ( zdepmoy(ji,jj) + rtrn )
279               epicom(ji,jj,jk) = zetmp5(ji,jj) * z1_dep
280            ENDIF
281         END_3D
282         DEALLOCATE( zetmp5 )
283      ENDIF
284      !
285      IF( lk_iomput .AND.  knt == nrdttrc ) THEN
286         CALL iom_put( "Heup" , heup(:,:  ) * tmask(:,:,1) )  ! euphotic layer deptht
287         IF( iom_use( "PAR" ) ) THEN
288            zpar(:,:,1) = zpar(:,:,1) * ( 1._wp - fr_i(:,:) )
289            CALL iom_put( "PAR", zpar(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation
290         ENDIF
291      ENDIF
292      !
293      IF( ln_timing )   CALL timing_stop('p4z_opt')
294      !
295   END SUBROUTINE p4z_opt
296
297
298   SUBROUTINE p4z_opt_par( kt, Kmm, pqsr, pe1, pe2, pe3, pe0, pqsr100 ) 
299      !!----------------------------------------------------------------------
300      !!                  ***  routine p4z_opt_par  ***
301      !!
302      !! ** purpose :   compute PAR of each wavelength (Red-Green-Blue)
303      !!                for a given shortwave radiation
304      !!
305      !!----------------------------------------------------------------------
306      INTEGER                         , INTENT(in)              ::   kt                ! ocean time-step
307      INTEGER                         , INTENT(in)              ::   Kmm               ! ocean time-index
308      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   )           ::   pqsr              ! shortwave
309      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)           ::   pe1 , pe2 , pe3   ! PAR ( R-G-B)
310      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout), OPTIONAL ::   pe0               !
311      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(  out), OPTIONAL ::   pqsr100           !
312      !
313      INTEGER    ::   ji, jj, jk     ! dummy loop indices
314      REAL(wp), DIMENSION(jpi,jpj) ::  zqsr   ! shortwave
315      !!----------------------------------------------------------------------
316
317      !  Real shortwave
318      IF( ln_varpar ) THEN  ;  zqsr(:,:) = par_varsw(:,:) * pqsr(:,:)
319      ELSE                  ;  zqsr(:,:) = xparsw         * pqsr(:,:)
320      ENDIF
321     
322      !  Light at the euphotic depth
323      IF( PRESENT( pqsr100 ) )   pqsr100(:,:) = 0.01 * 3. * zqsr(:,:)
324
325      IF( PRESENT( pe0 ) ) THEN     !  W-level
326         !
327         pe0(:,:,1) = pqsr(:,:) - 3. * zqsr(:,:)    !   ( 1 - 3 * alpha ) * q
328         pe1(:,:,1) = zqsr(:,:)         
329         pe2(:,:,1) = zqsr(:,:)
330         pe3(:,:,1) = zqsr(:,:)
331         !
332         DO_3D( 1, 1, 1, 1, 2, nksr + 1 )
333            pe0(ji,jj,jk) = pe0(ji,jj,jk-1) * EXP( -e3t(ji,jj,jk-1,Kmm) * xsi0r )
334            pe1(ji,jj,jk) = pe1(ji,jj,jk-1) * EXP( -ekb  (ji,jj,jk-1 )        )
335            pe2(ji,jj,jk) = pe2(ji,jj,jk-1) * EXP( -ekg  (ji,jj,jk-1 )        )
336            pe3(ji,jj,jk) = pe3(ji,jj,jk-1) * EXP( -ekr  (ji,jj,jk-1 )        )
337        END_3D
338        !
339      ELSE   ! T- level
340        !
341        pe1(:,:,1) = zqsr(:,:) * EXP( -0.5 * ekb(:,:,1) )
342        pe2(:,:,1) = zqsr(:,:) * EXP( -0.5 * ekg(:,:,1) )
343        pe3(:,:,1) = zqsr(:,:) * EXP( -0.5 * ekr(:,:,1) )
344        !
345        DO_3D( 1, 1, 1, 1, 2, nksr )
346           pe1(ji,jj,jk) = pe1(ji,jj,jk-1) * EXP( -0.5 * ( ekb(ji,jj,jk-1) + ekb(ji,jj,jk) ) )
347           pe2(ji,jj,jk) = pe2(ji,jj,jk-1) * EXP( -0.5 * ( ekg(ji,jj,jk-1) + ekg(ji,jj,jk) ) )
348           pe3(ji,jj,jk) = pe3(ji,jj,jk-1) * EXP( -0.5 * ( ekr(ji,jj,jk-1) + ekr(ji,jj,jk) ) )
349        END_3D
350        !
351      ENDIF
352      !
353   END SUBROUTINE p4z_opt_par
354
355
356   SUBROUTINE p4z_opt_sbc( kt )
357      !!----------------------------------------------------------------------
358      !!                  ***  routine p4z_opt_sbc  ***
359      !!
360      !! ** purpose :   read and interpolate the variable PAR fraction
361      !!                of shortwave radiation
362      !!
363      !! ** method  :   read the files and interpolate the appropriate variables
364      !!
365      !! ** input   :   external netcdf files
366      !!
367      !!----------------------------------------------------------------------
368      INTEGER, INTENT(in) ::   kt   ! ocean time step
369      !
370      INTEGER  :: ji,jj
371      REAL(wp) :: zcoef
372      !!---------------------------------------------------------------------
373      !
374      IF( ln_timing )  CALL timing_start('p4z_optsbc')
375      !
376      ! Compute par_varsw at nit000 or only if there is more than 1 time record in par coefficient file
377      IF( ln_varpar ) THEN
378         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_par > 1 ) ) THEN
379            CALL fld_read( kt, 1, sf_par )
380            par_varsw(:,:) = ( sf_par(1)%fnow(:,:,1) ) / 3.0
381         ENDIF
382      ENDIF
383      !
384      IF( ln_timing )  CALL timing_stop('p4z_optsbc')
385      !
386   END SUBROUTINE p4z_opt_sbc
387
388
389   SUBROUTINE p4z_opt_init
390      !!----------------------------------------------------------------------
391      !!                  ***  ROUTINE p4z_opt_init  ***
392      !!
393      !! ** Purpose :   Initialization of tabulated attenuation coef
394      !!                and of the percentage of PAR in Shortwave
395      !!
396      !! ** Input   :   external ascii and netcdf files
397      !!----------------------------------------------------------------------
398      INTEGER :: numpar, ierr, ios   ! Local integer
399      !
400      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
401      TYPE(FLD_N) ::   sn_par                ! informations about the fields to be read
402      !
403      NAMELIST/nampisopt/cn_dir, sn_par, ln_varpar, parlux
404      !!----------------------------------------------------------------------
405      IF(lwp) THEN
406         WRITE(numout,*)
407         WRITE(numout,*) 'p4z_opt_init : '
408         WRITE(numout,*) '~~~~~~~~~~~~ '
409      ENDIF
410      READ  ( numnatp_ref, nampisopt, IOSTAT = ios, ERR = 901)
411901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisopt in reference namelist' )
412      READ  ( numnatp_cfg, nampisopt, IOSTAT = ios, ERR = 902 )
413902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisopt in configuration namelist' )
414      IF(lwm) WRITE ( numonp, nampisopt )
415
416      IF(lwp) THEN
417         WRITE(numout,*) '   Namelist : nampisopt '
418         WRITE(numout,*) '      PAR as a variable fraction of SW     ln_varpar      = ', ln_varpar
419         WRITE(numout,*) '      Default value for the PAR fraction   parlux         = ', parlux
420      ENDIF
421      !
422      xparsw = parlux / 3.0
423      xsi0r  = 1.e0 / rn_si0
424      !
425      ! Variable PAR at the surface of the ocean
426      ! ----------------------------------------
427      IF( ln_varpar ) THEN
428         IF(lwp) WRITE(numout,*)
429         IF(lwp) WRITE(numout,*) '   ==>>>   initialize variable par fraction (ln_varpar=T)'
430         !
431         ALLOCATE( par_varsw(jpi,jpj) )
432         !
433         ALLOCATE( sf_par(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
434         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_opt_init: unable to allocate sf_par structure' )
435         !
436         CALL fld_fill( sf_par, (/ sn_par /), cn_dir, 'p4z_opt_init', 'Variable PAR fraction ', 'nampisopt' )
437                                   ALLOCATE( sf_par(1)%fnow(jpi,jpj,1)   )
438         IF( sn_par%ln_tint )      ALLOCATE( sf_par(1)%fdta(jpi,jpj,1,2) )
439
440         CALL iom_open (  TRIM( sn_par%clname ) , numpar )
441         ntimes_par = iom_getszuld( numpar )   ! get number of record in file
442      ENDIF
443      !
444                         ekr      (:,:,:) = 0._wp
445                         ekb      (:,:,:) = 0._wp
446                         ekg      (:,:,:) = 0._wp
447                         etot     (:,:,:) = 0._wp
448                         etot_ndcy(:,:,:) = 0._wp
449                         enano    (:,:,:) = 0._wp
450                         ediat    (:,:,:) = 0._wp
451      IF( ln_p5z     )   epico    (:,:,:) = 0._wp
452      IF( ln_qsr_bio )   etot3    (:,:,:) = 0._wp
453      !
454   END SUBROUTINE p4z_opt_init
455
456
457   INTEGER FUNCTION p4z_opt_alloc()
458      !!----------------------------------------------------------------------
459      !!                     ***  ROUTINE p4z_opt_alloc  ***
460      !!----------------------------------------------------------------------
461      !
462      ALLOCATE( ekb(jpi,jpj,jpk), ekr(jpi,jpj,jpk),  &
463                ekg(jpi,jpj,jpk), STAT= p4z_opt_alloc  ) 
464      !
465      IF( p4z_opt_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_opt_alloc : failed to allocate arrays.' )
466      !
467   END FUNCTION p4z_opt_alloc
468
469   !!======================================================================
470END MODULE p4zopt
Note: See TracBrowser for help on using the repository browser.