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/UKMO/dev_merge_2017_restart_datestamp_GO6_mixing/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/UKMO/dev_merge_2017_restart_datestamp_GO6_mixing/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90 @ 9496

Last change on this file since 9496 was 9496, checked in by davestorkey, 6 years ago

UKMO/branches/dev_merge_2017_restart_datestamp_GO6_mixing : clear SVN keywords.

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