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/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/p4zsbc.F90 @ 9240

Last change on this file since 9240 was 9240, checked in by cetlod, 6 years ago

v3.6 stable : bugfix on PISCES, see ticket #2003

  • Property svn:keywords set to Id
File size: 24.2 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
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
45   LOGICAL , PUBLIC  :: ll_sbc
46
47   !! * Module variables
48   LOGICAL  ::  ll_solub
49
50   INTEGER , PARAMETER  :: jpriv  = 7   !: Maximum number of river input fields
51   INTEGER , PARAMETER  :: jr_dic = 1   !: index of dissolved inorganic carbon
52   INTEGER , PARAMETER  :: jr_doc = 2   !: index of dissolved organic carbon
53   INTEGER , PARAMETER  :: jr_din = 3   !: index of dissolved inorganic nitrogen
54   INTEGER , PARAMETER  :: jr_don = 4   !: index of dissolved organic nitrogen
55   INTEGER , PARAMETER  :: jr_dip = 5   !: index of dissolved inorganic phosporus
56   INTEGER , PARAMETER  :: jr_dop = 6   !: index of dissolved organic phosphorus
57   INTEGER , PARAMETER  :: jr_dsi = 7   !: index of dissolved silicate
58
59
60   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_dust      ! structure of input dust
61   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub      ! structure of input dust
62   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river  ! structure of input riverdic
63   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ndepo     ! structure of input nitrogen deposition
64   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ironsed   ! structure of input iron from sediment
65   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_hydrofe   ! structure of input iron from hydrothermal vents
66
67   INTEGER , PARAMETER :: nbtimes = 365  !: maximum number of times record in a file
68   INTEGER  :: ntimes_dust, ntimes_riv, ntimes_ndep       ! number of time steps in a file
69   INTEGER  :: ntimes_solub, ntimes_hydro                 ! number of time steps in a file
70
71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: dust, solub       !: dust fields
72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdic, rivalk    !: river input fields
73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdin, rivdip    !: river input fields
74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdsi    !: river input fields
75   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: nitdep    !: atmospheric N deposition
76   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ironsed   !: Coastal supply of iron
77   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hydrofe   !: Hydrothermal vent supply of iron
78
79   REAL(wp), PUBLIC :: sumdepsi, rivalkinput, rivdicinput, nitdepinput
80   REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput
81
82
83   !!* Substitution
84#  include "top_substitute.h90"
85   !!----------------------------------------------------------------------
86   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
87   !! $Id$
88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
89   !!----------------------------------------------------------------------
90
91CONTAINS
92
93   SUBROUTINE p4z_sbc( kt )
94      !!----------------------------------------------------------------------
95      !!                  ***  routine p4z_sbc  ***
96      !!
97      !! ** purpose :   read and interpolate the external sources of nutrients
98      !!
99      !! ** method  :   read the files and interpolate the appropriate variables
100      !!
101      !! ** input   :   external netcdf files
102      !!
103      !!----------------------------------------------------------------------
104      !! * arguments
105      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
106
107      !! * local declarations
108      INTEGER  :: ji,jj 
109      REAL(wp) :: zcoef, zyyss
110      !!---------------------------------------------------------------------
111      !
112      IF( nn_timing == 1 )  CALL timing_start('p4z_sbc')
113
114      !
115      ! Compute dust at nit000 or only if there is more than 1 time record in dust file
116      IF( ln_dust ) THEN
117         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_dust > 1 ) ) THEN
118            CALL fld_read( kt, 1, sf_dust )
119            IF( nn_ice_tr == -1 .AND. .NOT. ln_ironice ) THEN
120               dust(:,:) = MAX( rtrn, sf_dust(1)%fnow(:,:,1) )
121            ELSE
122               dust(:,:) = MAX( rtrn, sf_dust(1)%fnow(:,:,1) ) * ( 1.0 - fr_i(:,:) ) 
123            ENDIF
124         ENDIF
125      ENDIF
126
127      IF( ll_solub ) THEN
128         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_solub > 1 ) ) THEN
129            CALL fld_read( kt, 1, sf_solub )
130            solub(:,:) = sf_solub(1)%fnow(:,:,1)
131         ENDIF
132      ENDIF
133
134      ! N/P and Si releases due to coastal rivers
135      ! Compute river at nit000 or only if there is more than 1 time record in river file
136      ! -----------------------------------------
137      IF( ln_river ) THEN
138         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_riv > 1 ) ) THEN
139            CALL fld_read( kt, 1, sf_river )
140            DO jj = 1, jpj
141               DO ji = 1, jpi
142                  zcoef = ryyss * e1e2t(ji,jj) * h_rnf(ji,jj) 
143                  rivalk(ji,jj) =   sf_river(jr_dic)%fnow(ji,jj,1)                                    &
144                     &              * 1.E3        / ( 12. * zcoef + rtrn )
145                  rivdic(ji,jj) = ( sf_river(jr_dic)%fnow(ji,jj,1) + sf_river(jr_doc)%fnow(ji,jj,1) ) &
146                     &              * 1.E3         / ( 12. * zcoef + rtrn )
147                  rivdin(ji,jj) = ( sf_river(jr_din)%fnow(ji,jj,1) + sf_river(jr_don)%fnow(ji,jj,1) ) &
148                     &              * 1.E3 / rno3 / ( 14. * zcoef + rtrn )
149                  rivdip(ji,jj) = ( sf_river(jr_dip)%fnow(ji,jj,1) + sf_river(jr_dop)%fnow(ji,jj,1) ) &
150                     &              * 1.E3 / po4r / ( 31. * zcoef + rtrn )
151                  rivdsi(ji,jj) =   sf_river(jr_dsi)%fnow(ji,jj,1)                                    &
152                     &              * 1.E3        / ( 28.1 * zcoef + rtrn )
153               END DO
154            END DO
155         ENDIF
156      ENDIF
157
158      ! Compute N deposition at nit000 or only if there is more than 1 time record in N deposition file
159      IF( ln_ndepo ) THEN
160         ! from kg m-2 s-1 to molC l-1 s-1
161         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_ndep > 1 ) ) THEN
162             zcoef = 14. * rno3
163             CALL fld_read( kt, 1, sf_ndepo )
164             nitdep(:,:) = MAX( rtrn, sf_ndepo(1)%fnow(:,:,1) ) / zcoef / fse3t(:,:,1) 
165         ENDIF
166         IF( lk_vvl ) THEN
167           zcoef = 14. * rno3
168           nitdep(:,:) = MAX ( rtrn, sf_ndepo(1)%fnow(:,:,1) ) / zcoef / fse3t(:,:,1) 
169         ENDIF
170      ENDIF
171      !
172      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc')
173      !
174   END SUBROUTINE p4z_sbc
175
176   SUBROUTINE p4z_sbc_init
177
178      !!----------------------------------------------------------------------
179      !!                  ***  routine p4z_sbc_init  ***
180      !!
181      !! ** purpose :   initialization of the external sources of nutrients
182      !!
183      !! ** method  :   read the files and compute the budget
184      !!                called at the first timestep (nittrc000)
185      !!
186      !! ** input   :   external netcdf files
187      !!
188      !!----------------------------------------------------------------------
189      !
190      INTEGER  :: ji, jj, jk, jm, ifpr
191      INTEGER  :: ii0, ii1, ij0, ij1
192      INTEGER  :: numdust, numsolub, numriv, numiron, numdepo, numhydro
193      INTEGER  :: ierr, ierr1, ierr2, ierr3
194      INTEGER  :: ios                 ! Local integer output status for namelist read
195      INTEGER  :: ik50                !  last level where depth less than 50 m
196      INTEGER  :: isrow             ! index for ORCA1 starting row
197      REAL(wp) :: zexpide, zdenitide, zmaskt
198      REAL(wp) :: ztimes_dust, ztimes_riv, ztimes_ndep 
199      REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records
200      REAL(wp), DIMENSION(:), ALLOCATABLE :: rivinput
201      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zriver, zcmask
202      !
203      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
204      TYPE(FLD_N), DIMENSION(jpriv) ::  slf_river    ! array of namelist informations on the fields to read
205      TYPE(FLD_N) ::   sn_dust, sn_solub, sn_ndepo, sn_ironsed, sn_hydrofe   ! informations about the fields to be read
206      TYPE(FLD_N) ::   sn_riverdoc, sn_riverdic, sn_riverdsi   ! informations about the fields to be read
207      TYPE(FLD_N) ::   sn_riverdin, sn_riverdon, sn_riverdip, sn_riverdop
208      !
209      NAMELIST/nampissbc/cn_dir, sn_dust, sn_solub, sn_riverdic, sn_riverdoc, sn_riverdin, sn_riverdon,     &
210        &                sn_riverdip, sn_riverdop, sn_riverdsi, sn_ndepo, sn_ironsed, sn_hydrofe, &
211        &                ln_dust, ln_solub, ln_river, ln_ndepo, ln_ironsed, ln_ironice, ln_hydrofe,    &
212        &                sedfeinput, dustsolub, icefeinput, wdust, mfrac, nitrfix, diazolight, concfediaz, hratio
213      !!----------------------------------------------------------------------
214      !
215      IF( nn_timing == 1 )  CALL timing_start('p4z_sbc_init')
216      !
217      !                            !* set file information
218      REWIND( numnatp_ref )              ! Namelist nampissbc in reference namelist : Pisces external sources of nutrients
219      READ  ( numnatp_ref, nampissbc, IOSTAT = ios, ERR = 901)
220901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp )
221
222      REWIND( numnatp_cfg )              ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients
223      READ  ( numnatp_cfg, nampissbc, IOSTAT = ios, ERR = 902 )
224902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp )
225      IF(lwm) WRITE ( numonp, nampissbc )
226
227      IF ( ( nn_ice_tr >= 0 ) .AND. ln_ironice ) THEN
228         IF(lwp) THEN
229            WRITE(numout,*) ' ln_ironice incompatible with nn_ice_tr = ', nn_ice_tr
230            WRITE(numout,*) ' Specify your sea ice iron concentration in nampisice instead '
231            WRITE(numout,*) ' ln_ironice is forced to .FALSE. '
232         ENDIF
233         ln_ironice = .FALSE.
234      ENDIF
235
236      IF(lwp) THEN
237         WRITE(numout,*) ' '
238         WRITE(numout,*) ' namelist : nampissbc '
239         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ '
240         WRITE(numout,*) '    dust input from the atmosphere           ln_dust     = ', ln_dust
241         WRITE(numout,*) '    Variable solubility of iron input        ln_solub    = ', ln_solub
242         WRITE(numout,*) '    river input of nutrients                 ln_river    = ', ln_river
243         WRITE(numout,*) '    atmospheric deposition of n              ln_ndepo    = ', ln_ndepo
244         WRITE(numout,*) '    Fe input from sediments                  ln_ironsed  = ', ln_ironsed
245         WRITE(numout,*) '    Fe input from seaice                     ln_ironice  = ', ln_ironice
246         WRITE(numout,*) '    fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe
247         WRITE(numout,*) '    coastal release of iron                  sedfeinput  = ', sedfeinput
248         WRITE(numout,*) '    solubility of the dust                   dustsolub   = ', dustsolub
249         WRITE(numout,*) '    Mineral Fe content of the dust           mfrac       = ', mfrac
250         WRITE(numout,*) '    Iron concentration in sea ice            icefeinput  = ', icefeinput
251         WRITE(numout,*) '    sinking speed of the dust                wdust       = ', wdust
252         WRITE(numout,*) '    nitrogen fixation rate                   nitrfix     = ', nitrfix
253         WRITE(numout,*) '    nitrogen fixation sensitivty to light    diazolight  = ', diazolight
254         WRITE(numout,*) '    fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz
255         WRITE(numout,*) '    Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio
256      END IF
257
258      IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN  ;  ll_sbc = .TRUE.
259      ELSE                                            ;  ll_sbc = .FALSE.
260      ENDIF
261
262      IF( ln_dust .AND. ln_solub ) THEN               ;  ll_solub = .TRUE.
263      ELSE                                            ;  ll_solub = .FALSE.
264      ENDIF
265
266
267      ! dust input from the atmosphere
268      ! ------------------------------
269      sumdepsi  = 0._wp
270      IF( ln_dust ) THEN 
271         !
272         IF(lwp) WRITE(numout,*) '    initialize dust input from atmosphere '
273         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
274         !
275         ALLOCATE( dust(jpi,jpj) )    ! allocation
276         !
277         ALLOCATE( sf_dust(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
278         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_dust structure' )
279         !
280         CALL fld_fill( sf_dust, (/ sn_dust /), cn_dir, 'p4z_sed_init', 'Atmospheric dust deposition', 'nampissed' )
281                                   ALLOCATE( sf_dust(1)%fnow(jpi,jpj,1)   )
282         IF( sn_dust%ln_tint )     ALLOCATE( sf_dust(1)%fdta(jpi,jpj,1,2) )
283         !
284         IF( Agrif_Root() ) THEN   !  Only on the master grid
285            ! Get total input dust ; need to compute total atmospheric supply of Si in a year
286            CALL iom_open (  TRIM( sn_dust%clname ) , numdust )
287            CALL iom_gettime( numdust, zsteps, kntime=ntimes_dust)  ! get number of record in file`
288         ENDIF
289      END IF
290
291      ! Solubility of dust deposition of iron
292      ! Only if ln_dust and ln_solubility set to true (ll_solub = .true.)
293      ! -----------------------------------------------------------------
294      IF( ll_solub ) THEN
295         !
296         IF(lwp) WRITE(numout,*) '    initialize variable solubility of Fe '
297         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
298         !
299         ALLOCATE( solub(jpi,jpj) )    ! allocation
300         !
301         ALLOCATE( sf_solub(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
302         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_solub structure' )
303         !
304         CALL fld_fill( sf_solub, (/ sn_solub /), cn_dir, 'p4z_sed_init', 'Solubility of atm. iron ', 'nampissed' )
305                                   ALLOCATE( sf_solub(1)%fnow(jpi,jpj,1)   )
306         IF( sn_solub%ln_tint )    ALLOCATE( sf_solub(1)%fdta(jpi,jpj,1,2) )
307         ! get number of record in file
308         CALL iom_open (  TRIM( sn_solub%clname ) , numsolub )
309         CALL iom_gettime( numsolub, zsteps, kntime=ntimes_solub)  ! get number of record in file
310         CALL iom_close( numsolub )
311      ENDIF
312
313      ! nutrient input from rivers
314      ! --------------------------
315      IF( ln_river ) THEN
316         !
317         slf_river(jr_dic) = sn_riverdic  ;  slf_river(jr_doc) = sn_riverdoc  ;  slf_river(jr_din) = sn_riverdin 
318         slf_river(jr_don) = sn_riverdon  ;  slf_river(jr_dip) = sn_riverdip  ;  slf_river(jr_dop) = sn_riverdop
319         slf_river(jr_dsi) = sn_riverdsi 
320         !
321         ALLOCATE( rivdic(jpi,jpj), rivalk(jpi,jpj), rivdin(jpi,jpj), rivdip(jpi,jpj), rivdsi(jpi,jpj) ) 
322         !
323         ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )           !* allocate and fill sf_river (forcing structure) with sn_river_
324         rivinput(:) = 0.0
325
326         IF( ierr1 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_irver structure' )
327         !
328         CALL fld_fill( sf_river, slf_river, cn_dir, 'p4z_sed_init', 'Input from river ', 'nampissed' )
329         DO ifpr = 1, jpriv
330                                          ALLOCATE( sf_river(ifpr)%fnow(jpi,jpj,1  ) )
331            IF( slf_river(ifpr)%ln_tint ) ALLOCATE( sf_river(ifpr)%fdta(jpi,jpj,1,2) )
332         END DO
333         IF( Agrif_Root() ) THEN   !  Only on the master grid
334            ! Get total input rivers ; need to compute total river supply in a year
335            DO ifpr = 1, jpriv
336               CALL iom_open ( TRIM( slf_river(ifpr)%clname ), numriv )
337               CALL iom_gettime( numriv, zsteps, kntime=ntimes_riv)
338               ALLOCATE( zriver(jpi,jpj,ntimes_riv) )
339               DO jm = 1, ntimes_riv
340                  CALL iom_get( numriv, jpdom_data, TRIM( slf_river(ifpr)%clvar ), zriver(:,:,jm), jm )
341               END DO
342               CALL iom_close( numriv )
343               ztimes_riv = 1._wp / FLOAT(ntimes_riv) 
344               DO jm = 1, ntimes_riv
345                  rivinput(ifpr) = rivinput(ifpr) + glob_sum( zriver(:,:,jm) * tmask(:,:,1) * ztimes_riv ) 
346               END DO
347               DEALLOCATE( zriver)
348            END DO
349            ! N/P and Si releases due to coastal rivers
350            ! -----------------------------------------
351            rivdicinput = (rivinput(jr_dic) + rivinput(jr_doc) ) * 1E3 / 12._wp
352            rivdininput = (rivinput(jr_din) + rivinput(jr_don) ) * 1E3 / rno3 / 14._wp
353            rivdipinput = (rivinput(jr_dip) + rivinput(jr_dop) ) * 1E3 / po4r / 31._wp
354            rivdsiinput = rivinput(jr_dsi) * 1E3 / 28.1_wp
355            rivalkinput = rivinput(jr_dic) * 1E3 / 12._wp
356            !
357         ENDIF
358      ELSE
359         rivdicinput = 0._wp
360         rivdininput = 0._wp
361         rivdipinput = 0._wp
362         rivdsiinput = 0._wp
363         rivalkinput = 0._wp
364      END IF 
365      ! nutrient input from dust
366      ! ------------------------
367      nitdepinput = 0._wp
368      IF( ln_ndepo ) THEN
369         !
370         IF(lwp) WRITE(numout,*) '    initialize the nutrient input by dust from ndeposition.orca.nc'
371         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
372         !
373         ALLOCATE( nitdep(jpi,jpj) )    ! allocation
374         !
375         ALLOCATE( sf_ndepo(1), STAT=ierr3 )           !* allocate and fill sf_sst (forcing structure) with sn_sst
376         IF( ierr3 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_ndepo structure' )
377         !
378         CALL fld_fill( sf_ndepo, (/ sn_ndepo /), cn_dir, 'p4z_sed_init', 'Nutrient atmospheric depositon ', 'nampissed' )
379                                   ALLOCATE( sf_ndepo(1)%fnow(jpi,jpj,1)   )
380         IF( sn_ndepo%ln_tint )    ALLOCATE( sf_ndepo(1)%fdta(jpi,jpj,1,2) )
381         !
382         IF( Agrif_Root() ) THEN   !  Only on the master grid
383            ! Get total input dust ; need to compute total atmospheric supply of N in a year
384            CALL iom_open ( TRIM( sn_ndepo%clname ), numdepo )
385            CALL iom_gettime( numdepo, zsteps, kntime=ntimes_ndep)
386         ENDIF
387      ENDIF
388
389      ! coastal and island masks
390      ! ------------------------
391      IF( ln_ironsed ) THEN     
392         !
393         IF(lwp) WRITE(numout,*) '    computation of an island mask to enhance coastal supply of iron'
394         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
395         !
396         ALLOCATE( ironsed(jpi,jpj,jpk) )    ! allocation
397         !
398         CALL iom_open ( TRIM( sn_ironsed%clname ), numiron )
399         ALLOCATE( zcmask(jpi,jpj,jpk) )
400         CALL iom_get  ( numiron, jpdom_data, TRIM( sn_ironsed%clvar ), zcmask(:,:,:), 1 )
401         CALL iom_close( numiron )
402         !
403         ik50 = 5        !  last level where depth less than 50 m
404         DO jk = jpkm1, 1, -1
405            IF( gdept_1d(jk) > 50. )  ik50 = jk - 1
406         END DO
407         IF (lwp) WRITE(numout,*)
408         IF (lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1)
409         IF (lwp) WRITE(numout,*)
410         DO jk = 1, ik50
411            DO jj = 2, jpjm1
412               DO ji = fs_2, fs_jpim1
413                  IF( tmask(ji,jj,jk) /= 0. ) THEN
414                     zmaskt = tmask(ji+1,jj,jk) * tmask(ji-1,jj,jk) * tmask(ji,jj+1,jk)    &
415                        &                       * tmask(ji,jj-1,jk) * tmask(ji,jj,jk+1)
416                     IF( zmaskt == 0. )   zcmask(ji,jj,jk ) = MAX( 0.1, zcmask(ji,jj,jk) ) 
417                  END IF
418               END DO
419            END DO
420         END DO
421         !
422         CALL lbc_lnk( zcmask , 'T', 1. )      ! lateral boundary conditions on cmask   (sign unchanged)
423         !
424         DO jk = 1, jpk
425            DO jj = 1, jpj
426               DO ji = 1, jpi
427                  zexpide   = MIN( 8.,( gdept_0(ji,jj,jk) / 500. )**(-1.5) )
428                  zdenitide = -0.9543 + 0.7662 * LOG( zexpide ) - 0.235 * LOG( zexpide )**2
429                  zcmask(ji,jj,jk) = zcmask(ji,jj,jk) * MIN( 1., EXP( zdenitide ) / 0.5 )
430               END DO
431            END DO
432         END DO
433         ! Coastal supply of iron
434         ! -------------------------
435         ironsed(:,:,jpk) = 0._wp
436         DO jk = 1, jpkm1
437            ironsed(:,:,jk) = sedfeinput * zcmask(:,:,jk) / ( e3t_0(:,:,jk) * rday )
438         END DO
439         DEALLOCATE( zcmask)
440      ENDIF
441      !
442      ! Iron from Hydrothermal vents
443      ! ------------------------
444      IF( ln_hydrofe ) THEN
445         !
446         IF(lwp) WRITE(numout,*) '    Input of iron from hydrothermal vents '
447         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
448         !
449         ALLOCATE( hydrofe(jpi,jpj,jpk) )    ! allocation
450         !
451         CALL iom_open ( TRIM( sn_hydrofe%clname ), numhydro )
452         CALL iom_get  ( numhydro, jpdom_data, TRIM( sn_hydrofe%clvar ), hydrofe(:,:,:), 1 )
453         CALL iom_close( numhydro )
454         !
455         DO jk = 1, jpk
456            hydrofe(:,:,jk) = ( hydrofe(:,:,jk) * hratio ) / ( e1e2t(:,:) * e3t_0(:,:,jk) * ryyss + rtrn ) / 1000._wp
457         ENDDO
458         !
459      ENDIF
460      !
461      IF( ll_sbc ) CALL p4z_sbc( nit000 ) 
462      !
463      IF(lwp) THEN
464         WRITE(numout,*)
465         WRITE(numout,*) '    Total input of elements from river supply'
466         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
467         WRITE(numout,*) '    N Supply   : ', rivdininput*rno3*1E3/1E12*14.,' TgN/yr'
468         WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1,' TgSi/yr'
469         WRITE(numout,*) '    P Supply   : ', rivdipinput*1E3*po4r/1E12*31.,' TgP/yr'
470         WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12,' Teq/yr'
471         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12,'TgC/yr'
472         WRITE(numout,*) 
473      ENDIF
474      !
475      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc_init')
476      !
477   END SUBROUTINE p4z_sbc_init
478
479#else
480   !!======================================================================
481   !!  Dummy module :                                   No PISCES bio-model
482   !!======================================================================
483CONTAINS
484   SUBROUTINE p4z_sbc                         ! Empty routine
485   END SUBROUTINE p4z_sbc
486#endif 
487
488   !!======================================================================
489END MODULE p4zsbc
Note: See TracBrowser for help on using the repository browser.