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.
p4zsbc.F90 in branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90 @ 6847

Last change on this file since 6847 was 6453, checked in by aumont, 8 years ago

New developments of PISCES (QUOTA, ligands, lability, ...)

  • Property svn:keywords set to Id
File size: 28.7 KB
Line 
1MODULE p4zsbc
2   !!======================================================================
3   !!                         ***  MODULE p4sbc  ***
4   !! TOP :   PISCES surface boundary conditions of external inputs of nutrients
5   !!======================================================================
6   !! History :   3.5  !  2012-07 (O. Aumont, C. Ethe) Original code
7   !!----------------------------------------------------------------------
8#if defined key_pisces || defined key_pisces_quota
9   !!----------------------------------------------------------------------
10   !!   'key_pisces'                                       PISCES bio-model
11   !!----------------------------------------------------------------------
12   !!   p4z_sbc        :  Read and interpolate time-varying nutrients fluxes
13   !!   p4z_sbc_init   :  Initialization of p4z_sbc
14   !!----------------------------------------------------------------------
15   USE oce_trc         !  shared variables between ocean and passive tracers
16   USE trc             !  passive tracers common variables
17   USE sms_pisces      !  PISCES Source Minus Sink variables
18   USE iom             !  I/O manager
19   USE fldread         !  time interpolation
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   p4z_sbc
25   PUBLIC   p4z_sbc_init   
26
27   !! * Shared module variables
28   LOGICAL , PUBLIC  :: ln_dust     !: boolean for dust input from the atmosphere
29   LOGICAL , PUBLIC  :: ln_solub    !: boolean for variable solubility of atmospheric iron
30   LOGICAL , PUBLIC  :: ln_river    !: boolean for river input of nutrients
31   LOGICAL , PUBLIC  :: ln_ndepo    !: boolean for atmospheric deposition of N
32   LOGICAL , PUBLIC  :: ln_ironsed  !: boolean for Fe input from sediments
33   LOGICAL , PUBLIC  :: ln_hydrofe  !: boolean for Fe input from hydrothermal vents
34   LOGICAL , PUBLIC  :: ln_ironice  !: boolean for Fe input from sea ice
35   REAL(wp), PUBLIC  :: sedfeinput  !: Coastal release of Iron
36   REAL(wp), PUBLIC  :: dustsolub   !: Solubility of the dust
37   REAL(wp), PUBLIC  :: mfrac       !: Mineral Content of the dust
38   REAL(wp), PUBLIC  :: icefeinput  !: Iron concentration in sea ice
39   REAL(wp), PUBLIC  :: wdust       !: Sinking speed of the dust
40   REAL(wp), PUBLIC  :: nitrfix     !: Nitrogen fixation rate   
41   REAL(wp), PUBLIC  :: diazolight  !: Nitrogen fixation sensitivty to light
42   REAL(wp), PUBLIC  :: concfediaz  !: Fe half-saturation Cste for diazotrophs
43   REAL(wp)          :: hratio      !: Fe:3He ratio assumed for vent iron supply
44#if defined key_ligand
45   REAL(wp), PUBLIC  :: fep_rats    !: Fep/Fer ratio from sed  sources
46   REAL(wp), PUBLIC  :: fep_rath    !: Fep/Fer ratio from hydro sources
47#endif
48
49   LOGICAL , PUBLIC  :: ll_sbc
50
51   !! * Module variables
52   LOGICAL  ::  ll_solub
53
54   INTEGER , PARAMETER  :: jpriv  = 7   !: Maximum number of river input fields
55   INTEGER , PARAMETER  :: jr_dic = 1   !: index of dissolved inorganic carbon
56   INTEGER , PARAMETER  :: jr_doc = 2   !: index of dissolved organic carbon
57   INTEGER , PARAMETER  :: jr_din = 3   !: index of dissolved inorganic nitrogen
58   INTEGER , PARAMETER  :: jr_don = 4   !: index of dissolved organic nitrogen
59   INTEGER , PARAMETER  :: jr_dip = 5   !: index of dissolved inorganic phosporus
60   INTEGER , PARAMETER  :: jr_dop = 6   !: index of dissolved organic phosphorus
61   INTEGER , PARAMETER  :: jr_dsi = 7   !: index of dissolved silicate
62
63
64   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_dust      ! structure of input dust
65   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub      ! structure of input dust
66   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river  ! structure of input riverdic
67   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ndepo     ! structure of input nitrogen deposition
68   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ironsed   ! structure of input iron from sediment
69   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_hydrofe   ! structure of input iron from hydrothermal vents
70
71   INTEGER , PARAMETER :: nbtimes = 365  !: maximum number of times record in a file
72   INTEGER  :: ntimes_dust, ntimes_riv, ntimes_ndep       ! number of time steps in a file
73   INTEGER  :: ntimes_solub, ntimes_hydro                 ! number of time steps in a file
74
75   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: dust, solub       !: dust fields
76   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdic, rivalk    !: river input fields
77   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdin, rivdip    !: river input fields
78#if defined key_pisces_quota
79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdon, rivdop    !: river input fields
80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdoc    !: river input fields
81#endif
82   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdsi    !: river input fields
83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: nitdep    !: atmospheric N deposition
84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ironsed   !: Coastal supply of iron
85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hydrofe   !: Hydrothermal vent supply of iron
86
87   REAL(wp), PUBLIC :: sumdepsi, rivalkinput, rivdicinput, nitdepinput
88   REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput
89
90   !!* Substitution
91#  include "top_substitute.h90"
92   !!----------------------------------------------------------------------
93   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
94   !! $Header:$
95   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
96   !!----------------------------------------------------------------------
97
98CONTAINS
99
100   SUBROUTINE p4z_sbc( kt )
101      !!----------------------------------------------------------------------
102      !!                  ***  routine p4z_sbc  ***
103      !!
104      !! ** purpose :   read and interpolate the external sources of nutrients
105      !!
106      !! ** method  :   read the files and interpolate the appropriate variables
107      !!
108      !! ** input   :   external netcdf files
109      !!
110      !!----------------------------------------------------------------------
111      !! * arguments
112      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
113
114      !! * local declarations
115      INTEGER  :: ji,jj 
116      REAL(wp) :: zcoef, zyyss
117      !!---------------------------------------------------------------------
118      !
119      IF( nn_timing == 1 )  CALL timing_start('p4z_sbc')
120
121      !
122      ! Compute dust at nit000 or only if there is more than 1 time record in dust file
123      IF( ln_dust ) THEN
124         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_dust > 1 ) ) THEN
125            CALL fld_read( kt, 1, sf_dust )
126            IF( nn_ice_tr == -1 .AND. .NOT. ln_ironice ) THEN
127               dust(:,:) = sf_dust(1)%fnow(:,:,1)
128            ELSE
129               dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.0 - fr_i(:,:) )
130            ENDIF
131         ENDIF
132      ENDIF
133
134      IF( ll_solub ) THEN
135         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_solub > 1 ) ) THEN
136            CALL fld_read( kt, 1, sf_solub )
137            solub(:,:) = sf_solub(1)%fnow(:,:,1)
138         ENDIF
139      ENDIF
140
141      ! N/P and Si releases due to coastal rivers
142      ! Compute river at nit000 or only if there is more than 1 time record in river file
143      ! -----------------------------------------
144      IF( ln_river ) THEN
145         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_riv > 1 ) ) THEN
146            CALL fld_read( kt, 1, sf_river )
147            DO jj = 1, jpj
148               DO ji = 1, jpi
149                  zcoef = ryyss * cvol(ji,jj,1) 
150                  rivalk(ji,jj) =   sf_river(jr_dic)%fnow(ji,jj,1)                                    &
151                     &              * 1.E3 / ( 12. * zcoef + rtrn ) * tmask(ji,jj,1)
152#if defined key_pisces_quota
153                  rivdic(ji,jj) = ( sf_river(jr_dic)%fnow(ji,jj,1) ) &
154                     &              * 1.E3 / ( 12. * zcoef + rtrn ) * tmask(ji,jj,1)
155                  rivdin(ji,jj) = ( sf_river(jr_din)%fnow(ji,jj,1) ) &
156                     &              * 1.E3 / rno3 / ( 14. * zcoef + rtrn ) * tmask(ji,jj,1)
157                  rivdip(ji,jj) = ( sf_river(jr_dip)%fnow(ji,jj,1) ) &
158                     &              * 1.E3 / po4r / ( 31. * zcoef + rtrn ) * tmask(ji,jj,1)
159                  rivdoc(ji,jj) = ( sf_river(jr_doc)%fnow(ji,jj,1) ) &
160                     &              * 1.E3 / ( 12. * zcoef + rtrn ) * tmask(ji,jj,1)
161                  rivdon(ji,jj) = ( sf_river(jr_don)%fnow(ji,jj,1) ) &
162                     &              * 1.E3 / rno3 / ( 14. * zcoef + rtrn ) * tmask(ji,jj,1)
163                  rivdop(ji,jj) = ( sf_river(jr_dop)%fnow(ji,jj,1) ) &
164                     &              * 1.E3 / po4r / ( 31. * zcoef + rtrn ) * tmask(ji,jj,1)
165#else
166                  rivdic(ji,jj) = ( sf_river(jr_dic)%fnow(ji,jj,1) + sf_river(jr_doc)%fnow(ji,jj,1) ) &
167                     &              * 1.E3 / ( 12. * zcoef + rtrn ) * tmask(ji,jj,1)
168                  rivdin(ji,jj) = ( sf_river(jr_din)%fnow(ji,jj,1) + sf_river(jr_don)%fnow(ji,jj,1) ) &
169                     &              * 1.E3 / rno3 / ( 14. * zcoef + rtrn ) * tmask(ji,jj,1)
170                  rivdip(ji,jj) = ( sf_river(jr_dip)%fnow(ji,jj,1) + sf_river(jr_dop)%fnow(ji,jj,1) ) &
171                     &              * 1.E3 / po4r / ( 31. * zcoef + rtrn ) * tmask(ji,jj,1)
172#endif
173                  rivdsi(ji,jj) =   sf_river(jr_dsi)%fnow(ji,jj,1)                                    &
174                     &              * 1.E3 / ( 28.1 * zcoef + rtrn ) * tmask(ji,jj,1)
175               END DO
176            END DO
177         ENDIF
178      ENDIF
179
180      ! Compute N deposition at nit000 or only if there is more than 1 time record in N deposition file
181      IF( ln_ndepo ) THEN
182         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_ndep > 1 ) ) THEN
183            CALL fld_read( kt, 1, sf_ndepo )
184            DO jj = 1, jpj
185               DO ji = 1, jpi
186                  nitdep(ji,jj) = sf_ndepo(1)%fnow(ji,jj,1) / rno3 / ( 14E6 * ryyss * fse3t(ji,jj,1) + rtrn )
187               END DO
188            END DO
189         ENDIF
190      ENDIF
191      !
192      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc')
193      !
194   END SUBROUTINE p4z_sbc
195
196   SUBROUTINE p4z_sbc_init
197
198      !!----------------------------------------------------------------------
199      !!                  ***  routine p4z_sbc_init  ***
200      !!
201      !! ** purpose :   initialization of the external sources of nutrients
202      !!
203      !! ** method  :   read the files and compute the budget
204      !!                called at the first timestep (nittrc000)
205      !!
206      !! ** input   :   external netcdf files
207      !!
208      !!----------------------------------------------------------------------
209      !
210      INTEGER  :: ji, jj, jk, jm, ifpr
211      INTEGER  :: ii0, ii1, ij0, ij1
212      INTEGER  :: numdust, numsolub, numriv, numiron, numdepo, numhydro
213      INTEGER  :: ierr, ierr1, ierr2, ierr3
214      INTEGER  :: ios                 ! Local integer output status for namelist read
215      INTEGER  :: ik50                !  last level where depth less than 50 m
216      REAL(wp) :: zexpide, zdenitide, zmaskt
217      REAL(wp) :: ztimes_dust, ztimes_riv, ztimes_ndep 
218      REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records
219      REAL(wp), DIMENSION(:), ALLOCATABLE :: rivinput
220      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zdust, zndepo, zriver, zcmask
221      !
222      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
223      TYPE(FLD_N), DIMENSION(jpriv) ::  slf_river    ! array of namelist informations on the fields to read
224      TYPE(FLD_N) ::   sn_dust, sn_solub, sn_ndepo, sn_ironsed, sn_hydrofe   ! informations about the fields to be read
225      TYPE(FLD_N) ::   sn_riverdoc, sn_riverdic, sn_riverdsi   ! informations about the fields to be read
226      TYPE(FLD_N) ::   sn_riverdin, sn_riverdon, sn_riverdip, sn_riverdop
227      !
228      NAMELIST/nampissbc/cn_dir, sn_dust, sn_solub, sn_riverdic, sn_riverdoc, sn_riverdin, sn_riverdon,     &
229        &                sn_riverdip, sn_riverdop, sn_riverdsi, sn_ndepo, sn_ironsed, sn_hydrofe, &
230        &                ln_dust, ln_solub, ln_river, ln_ndepo, ln_ironsed, ln_ironice, ln_hydrofe,    &
231        &                sedfeinput, dustsolub, icefeinput, wdust, mfrac, nitrfix, diazolight, concfediaz,   &
232#if defined key_ligand
233        &                fep_rats, fep_rath,                     &
234#endif
235        &                hratio
236      !!----------------------------------------------------------------------
237      !
238      IF( nn_timing == 1 )  CALL timing_start('p4z_sbc_init')
239      !
240      !                            !* set file information
241      REWIND( numnatp_ref )              ! Namelist nampissbc in reference namelist : Pisces external sources of nutrients
242      READ  ( numnatp_ref, nampissbc, IOSTAT = ios, ERR = 901)
243901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp )
244
245      REWIND( numnatp_cfg )              ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients
246      READ  ( numnatp_cfg, nampissbc, IOSTAT = ios, ERR = 902 )
247902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp )
248      IF(lwm) WRITE ( numonp, nampissbc )
249
250      IF(lwp) THEN
251         WRITE(numout,*) ' '
252         WRITE(numout,*) ' namelist : nampissbc '
253         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ '
254         WRITE(numout,*) '    dust input from the atmosphere           ln_dust     = ', ln_dust
255         WRITE(numout,*) '    Variable solubility of iron input        ln_solub    = ', ln_solub
256         WRITE(numout,*) '    river input of nutrients                 ln_river    = ', ln_river
257         WRITE(numout,*) '    atmospheric deposition of n              ln_ndepo    = ', ln_ndepo
258         WRITE(numout,*) '    Fe input from sediments                  ln_ironsed  = ', ln_ironsed
259         WRITE(numout,*) '    Fe input from seaice                     ln_ironice  = ', ln_ironice
260         WRITE(numout,*) '    fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe
261         WRITE(numout,*) '    coastal release of iron                  sedfeinput  = ', sedfeinput
262         WRITE(numout,*) '    solubility of the dust                   dustsolub   = ', dustsolub
263         WRITE(numout,*) '    Mineral Fe content of the dust           mfrac       = ', mfrac
264         WRITE(numout,*) '    Iron concentration in sea ice            icefeinput  = ', icefeinput
265         WRITE(numout,*) '    sinking speed of the dust                wdust       = ', wdust
266         WRITE(numout,*) '    nitrogen fixation rate                   nitrfix     = ', nitrfix
267         WRITE(numout,*) '    nitrogen fixation sensitivty to light    diazolight  = ', diazolight
268         WRITE(numout,*) '    fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz
269         WRITE(numout,*) '    Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio
270#if defined key_ligand
271         WRITE(numout,*) '    Fep/Fer ratio from sed sources                       = ', fep_rats
272         WRITE(numout,*) '    Fep/Fer ratio from sed hydro sources                 = ', fep_rath
273#endif
274      END IF
275
276      IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN  ;  ll_sbc = .TRUE.
277      ELSE                                            ;  ll_sbc = .FALSE.
278      ENDIF
279
280      IF( ln_dust .AND. ln_solub ) THEN               ;  ll_solub = .TRUE.
281      ELSE                                            ;  ll_solub = .FALSE.
282      ENDIF
283
284      ! set the number of level over which river runoffs are applied
285      ! online configuration : computed in sbcrnf
286      IF( lk_offline ) THEN
287        nk_rnf(:,:) = 1
288        h_rnf (:,:) = fsdept(:,:,1)
289      ENDIF
290
291      ! dust input from the atmosphere
292      ! ------------------------------
293      IF( ln_dust ) THEN 
294         !
295         IF(lwp) WRITE(numout,*) '    initialize dust input from atmosphere '
296         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
297         !
298         ALLOCATE( dust(jpi,jpj) )    ! allocation
299         !
300         ALLOCATE( sf_dust(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
301         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_dust structure' )
302         !
303         CALL fld_fill( sf_dust, (/ sn_dust /), cn_dir, 'p4z_sed_init', 'Atmospheric dust deposition', 'nampissed' )
304                                   ALLOCATE( sf_dust(1)%fnow(jpi,jpj,1)   )
305         IF( sn_dust%ln_tint )     ALLOCATE( sf_dust(1)%fdta(jpi,jpj,1,2) )
306         !
307         IF( Agrif_Root() ) THEN   !  Only on the master grid
308            ! Get total input dust ; need to compute total atmospheric supply of Si in a year
309            CALL iom_open (  TRIM( sn_dust%clname ) , numdust )
310            CALL iom_gettime( numdust, zsteps, kntime=ntimes_dust)  ! get number of record in file
311            ALLOCATE( zdust(jpi,jpj,ntimes_dust) )
312            DO jm = 1, ntimes_dust
313               CALL iom_get( numdust, jpdom_data, TRIM( sn_dust%clvar ), zdust(:,:,jm), jm )
314            END DO
315            CALL iom_close( numdust )
316            ztimes_dust = 1._wp / FLOAT( ntimes_dust ) 
317            sumdepsi = 0.e0
318            DO jm = 1, ntimes_dust
319               sumdepsi = sumdepsi + glob_sum( zdust(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_dust )
320            ENDDO
321            sumdepsi = sumdepsi / ( nyear_len(1) * rday ) * 12. * 8.8 * 0.075 * mfrac / 28.1 
322            DEALLOCATE( zdust)
323         ENDIF
324      ELSE
325         sumdepsi  = 0._wp
326      END IF
327
328      ! Solubility of dust deposition of iron
329      ! Only if ln_dust and ln_solubility set to true (ll_solub = .true.)
330      ! -----------------------------------------------------------------
331      IF( ll_solub ) THEN
332         !
333         IF(lwp) WRITE(numout,*) '    initialize variable solubility of Fe '
334         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
335         !
336         ALLOCATE( solub(jpi,jpj) )    ! allocation
337         !
338         ALLOCATE( sf_solub(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
339         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_solub structure' )
340         !
341         CALL fld_fill( sf_solub, (/ sn_solub /), cn_dir, 'p4z_sed_init', 'Solubility of atm. iron ', 'nampissed' )
342                                   ALLOCATE( sf_solub(1)%fnow(jpi,jpj,1)   )
343         IF( sn_solub%ln_tint )    ALLOCATE( sf_solub(1)%fdta(jpi,jpj,1,2) )
344         ! get number of record in file
345         CALL iom_open (  TRIM( sn_solub%clname ) , numsolub )
346         CALL iom_gettime( numsolub, zsteps, kntime=ntimes_solub)  ! get number of record in file
347         CALL iom_close( numsolub )
348      ENDIF
349
350      ! nutrient input from rivers
351      ! --------------------------
352      IF( ln_river ) THEN
353         !
354         slf_river(jr_dic) = sn_riverdic  ;  slf_river(jr_doc) = sn_riverdoc  ;  slf_river(jr_din) = sn_riverdin 
355         slf_river(jr_don) = sn_riverdon  ;  slf_river(jr_dip) = sn_riverdip  ;  slf_river(jr_dop) = sn_riverdop
356         slf_river(jr_dsi) = sn_riverdsi 
357         !
358         ALLOCATE( rivdic(jpi,jpj), rivalk(jpi,jpj), rivdin(jpi,jpj), rivdip(jpi,jpj), rivdsi(jpi,jpj) ) 
359#if defined key_pisces_quota
360         ALLOCATE( rivdon(jpi,jpj), rivdop(jpi,jpj), rivdoc(jpi,jpj) )
361#endif
362         !
363         ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )           !* allocate and fill sf_river (forcing structure) with sn_river_
364         rivinput(:) = 0.0
365
366         IF( ierr1 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_irver structure' )
367         !
368         CALL fld_fill( sf_river, slf_river, cn_dir, 'p4z_sed_init', 'Input from river ', 'nampissed' )
369         DO ifpr = 1, jpriv
370                                          ALLOCATE( sf_river(ifpr)%fnow(jpi,jpj,1  ) )
371            IF( slf_river(ifpr)%ln_tint ) ALLOCATE( sf_river(ifpr)%fdta(jpi,jpj,1,2) )
372         END DO
373         IF( Agrif_Root() ) THEN   !  Only on the master grid
374            ! Get total input rivers ; need to compute total river supply in a year
375            DO ifpr = 1, jpriv
376               CALL iom_open ( TRIM( slf_river(ifpr)%clname ), numriv )
377               CALL iom_gettime( numriv, zsteps, kntime=ntimes_riv)
378               ALLOCATE( zriver(jpi,jpj,ntimes_riv) )
379               DO jm = 1, ntimes_riv
380                  CALL iom_get( numriv, jpdom_data, TRIM( slf_river(ifpr)%clvar ), zriver(:,:,jm), jm )
381               END DO
382               CALL iom_close( numriv )
383               ztimes_riv = 1._wp / FLOAT(ntimes_riv) 
384               DO jm = 1, ntimes_riv
385                  rivinput(ifpr) = rivinput(ifpr) + glob_sum( zriver(:,:,jm) * tmask(:,:,1) * ztimes_riv ) 
386               END DO
387               DEALLOCATE( zriver)
388            END DO
389            ! N/P and Si releases due to coastal rivers
390            ! -----------------------------------------
391            rivdicinput = (rivinput(jr_dic) + rivinput(jr_doc) ) * 1E3 / 12._wp
392            rivdininput = (rivinput(jr_din) + rivinput(jr_don) ) * 1E3 / rno3 / 14._wp
393            rivdipinput = (rivinput(jr_dip) + rivinput(jr_dop) ) * 1E3 / po4r / 31._wp
394            rivdsiinput = rivinput(jr_dsi) * 1E3 / 28.1_wp
395            rivalkinput = rivinput(jr_dic) * 1E3 / 12._wp
396            !
397         ENDIF
398      ELSE
399         rivdicinput = 0._wp
400         rivdininput = 0._wp
401         rivdipinput = 0._wp
402         rivdsiinput = 0._wp
403         rivalkinput = 0._wp
404      END IF 
405
406      ! nutrient input from dust
407      ! ------------------------
408      IF( ln_ndepo ) THEN
409         !
410         IF(lwp) WRITE(numout,*) '    initialize the nutrient input by dust from ndeposition.orca.nc'
411         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
412         !
413         ALLOCATE( nitdep(jpi,jpj) )    ! allocation
414         !
415         ALLOCATE( sf_ndepo(1), STAT=ierr3 )           !* allocate and fill sf_sst (forcing structure) with sn_sst
416         IF( ierr3 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_ndepo structure' )
417         !
418         CALL fld_fill( sf_ndepo, (/ sn_ndepo /), cn_dir, 'p4z_sed_init', 'Nutrient atmospheric depositon ', 'nampissed' )
419                                   ALLOCATE( sf_ndepo(1)%fnow(jpi,jpj,1)   )
420         IF( sn_ndepo%ln_tint )    ALLOCATE( sf_ndepo(1)%fdta(jpi,jpj,1,2) )
421         !
422         IF( Agrif_Root() ) THEN   !  Only on the master grid
423            ! Get total input dust ; need to compute total atmospheric supply of N in a year
424            CALL iom_open ( TRIM( sn_ndepo%clname ), numdepo )
425            CALL iom_gettime( numdepo, zsteps, kntime=ntimes_ndep)
426            ALLOCATE( zndepo(jpi,jpj,ntimes_ndep) )
427            DO jm = 1, ntimes_ndep
428               CALL iom_get( numdepo, jpdom_data, TRIM( sn_ndepo%clvar ), zndepo(:,:,jm), jm )
429            END DO
430            CALL iom_close( numdepo )
431            ztimes_ndep = 1._wp / FLOAT( ntimes_ndep ) 
432            nitdepinput = 0._wp
433            DO jm = 1, ntimes_ndep
434              nitdepinput = nitdepinput + glob_sum( zndepo(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_ndep )
435            ENDDO
436            nitdepinput = nitdepinput / rno3 / 14E6 
437            DEALLOCATE( zndepo)
438         ENDIF
439      ELSE
440         nitdepinput = 0._wp
441      ENDIF
442
443      ! coastal and island masks
444      ! ------------------------
445      IF( ln_ironsed ) THEN     
446         !
447         IF(lwp) WRITE(numout,*) '    computation of an island mask to enhance coastal supply of iron'
448         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
449         !
450         ALLOCATE( ironsed(jpi,jpj,jpk) )    ! allocation
451         !
452         CALL iom_open ( TRIM( sn_ironsed%clname ), numiron )
453         ALLOCATE( zcmask(jpi,jpj,jpk) )
454         CALL iom_get  ( numiron, jpdom_data, TRIM( sn_ironsed%clvar ), zcmask(:,:,:), 1 )
455         CALL iom_close( numiron )
456         !
457         ik50 = 5        !  last level where depth less than 50 m
458         DO jk = jpkm1, 1, -1
459            IF( gdept_1d(jk) > 50. )  ik50 = jk - 1
460         END DO
461         IF (lwp) WRITE(numout,*)
462         IF (lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1)
463         IF (lwp) WRITE(numout,*)
464         DO jk = 1, ik50
465            DO jj = 2, jpjm1
466               DO ji = fs_2, fs_jpim1
467                  IF( tmask(ji,jj,jk) /= 0. ) THEN
468                     zmaskt = tmask(ji+1,jj,jk) * tmask(ji-1,jj,jk) * tmask(ji,jj+1,jk)    &
469                        &                       * tmask(ji,jj-1,jk) * tmask(ji,jj,jk+1)
470                     IF( zmaskt == 0. )   zcmask(ji,jj,jk ) = MAX( 0.1, zcmask(ji,jj,jk) ) 
471                  END IF
472               END DO
473            END DO
474         END DO
475         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 ) THEN
476            ii0 = 176   ;   ii1 =  176        ! Southern Island : Kerguelen
477            ij0 =  37   ;   ij1 =   37  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
478            !
479            ii0 = 119   ;   ii1 =  119        ! South Georgia
480            ij0 =  29   ;   ij1 =   29  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
481            !
482            ii0 = 111   ;   ii1 =  111        ! Falklands
483            ij0 =  35   ;   ij1 =   35  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
484            !
485            ii0 = 168   ;   ii1 =  168        ! Crozet
486            ij0 =  40   ;   ij1 =   40  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
487            !
488            ii0 = 119   ;   ii1 =  119        ! South Orkney
489            ij0 =  28   ;   ij1 =   28  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
490            !
491            ii0 = 140   ;   ii1 =  140        ! Bouvet Island
492            ij0 =  33   ;   ij1 =   33  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
493            !
494            ii0 = 178   ;   ii1 =  178        ! Prince edwards
495            ij0 =  34   ;   ij1 =   34  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
496            !
497            ii0 =  43   ;   ii1 =   43        ! Balleny islands
498            ij0 =  21   ;   ij1 =   21  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
499         ENDIF
500         CALL lbc_lnk( zcmask , 'T', 1. )      ! lateral boundary conditions on cmask   (sign unchanged)
501         DO jk = 1, jpk
502            DO jj = 1, jpj
503               DO ji = 1, jpi
504                  zexpide   = MIN( 8.,( fsdept(ji,jj,jk) / 500. )**(-1.5) )
505                  zdenitide = -0.9543 + 0.7662 * LOG( zexpide ) - 0.235 * LOG( zexpide )**2
506                  zcmask(ji,jj,jk) = zcmask(ji,jj,jk) * MIN( 1., EXP( zdenitide ) / 0.5 ) * tmask(ji,jj,jk)
507               END DO
508            END DO
509         END DO
510         ! Coastal supply of iron
511         ! -------------------------
512         ironsed(:,:,jpk) = 0._wp
513         DO jk = 1, jpkm1
514            ironsed(:,:,jk) = sedfeinput * zcmask(:,:,jk) / ( fse3t(:,:,jk) * rday ) 
515         END DO
516         DEALLOCATE( zcmask)
517      ENDIF
518      !
519      ! Iron from Hydrothermal vents
520      ! ------------------------
521      IF( ln_hydrofe ) THEN
522         !
523         IF(lwp) WRITE(numout,*) '    Input of iron from hydrothermal vents '
524         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
525         !
526         ALLOCATE( hydrofe(jpi,jpj,jpk) )    ! allocation
527         !
528         CALL iom_open ( TRIM( sn_hydrofe%clname ), numhydro )
529         CALL iom_get  ( numhydro, jpdom_data, TRIM( sn_hydrofe%clvar ), hydrofe(:,:,:), 1 )
530         CALL iom_close( numhydro )
531         !
532         hydrofe(:,:,:) = ( hydrofe(:,:,:) * hratio ) / ( cvol(:,:,:) * ryyss + rtrn ) / 1000._wp * tmask(:,:,:)
533         !
534      ENDIF
535      !
536      IF( ll_sbc ) CALL p4z_sbc( nit000 ) 
537      !
538      IF(lwp) THEN
539         WRITE(numout,*)
540         WRITE(numout,*) '    Total input of elements from river supply'
541         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
542         WRITE(numout,*) '    N Supply   : ', rivdininput*rno3*1E3/1E12*14.,' TgN/yr'
543         WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1,' TgSi/yr'
544         WRITE(numout,*) '    P Supply   : ', rivdipinput*1E3*po4r/1E12*31.,' TgP/yr'
545         WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12,' Teq/yr'
546         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12,'TgC/yr'
547         WRITE(numout,*) 
548         WRITE(numout,*) '    Total input of elements from atmospheric supply'
549         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
550         WRITE(numout,*) '    N Supply   : ', nitdepinput*rno3*1E3/1E12*14.,' TgN/yr'
551         WRITE(numout,*) 
552      ENDIF
553      !
554      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc_init')
555      !
556   END SUBROUTINE p4z_sbc_init
557
558#else
559   !!======================================================================
560   !!  Dummy module :                                   No PISCES bio-model
561   !!======================================================================
562CONTAINS
563   SUBROUTINE p4z_sbc                         ! Empty routine
564   END SUBROUTINE p4z_sbc
565#endif 
566
567   !!======================================================================
568END MODULE  p4zsbc
Note: See TracBrowser for help on using the repository browser.