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/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90 @ 3451

Last change on this file since 3451 was 3451, checked in by cetlod, 12 years ago

banch:2012/dev_r3438_LOCEAN15_PISLOB : minor bug corrections, see ticket #972

File size: 27.1 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     = .FALSE.    !: boolean for dust input from the atmosphere
29   LOGICAL , PUBLIC  :: ln_solub    = .FALSE.    !: boolean for variable solubility of atmospheric iron
30   LOGICAL , PUBLIC  :: ln_river    = .FALSE.    !: boolean for river input of nutrients
31   LOGICAL , PUBLIC  :: ln_ndepo    = .FALSE.    !: boolean for atmospheric deposition of N
32   LOGICAL , PUBLIC  :: ln_ironsed  = .FALSE.    !: boolean for Fe input from sediments
33   LOGICAL , PUBLIC  :: ln_hydrofe  = .FALSE.    !: boolean for Fe input from hydrothermal vents
34   LOGICAL , PUBLIC  :: ln_ironice  = .FALSE.    !: boolean for Fe input from sea ice
35   REAL(wp), PUBLIC  :: sedfeinput  = 1.E-9_wp   !: Coastal release of Iron
36   REAL(wp), PUBLIC  :: dustsolub   = 0.014_wp   !: Solubility of the dust
37   REAL(wp), PUBLIC  :: icefeinput  = 10E-9_wp   !: Iron concentration in sea ice
38   REAL(wp), PUBLIC  :: wdust       = 2.0_wp     !: Sinking speed of the dust
39   REAL(wp), PUBLIC  :: nitrfix     = 1E-7_wp    !: Nitrogen fixation rate   
40   REAL(wp), PUBLIC  :: diazolight  = 50._wp     !: Nitrogen fixation sensitivty to light
41   REAL(wp), PUBLIC  :: concfediaz  = 1.E-10_wp  !: Fe half-saturation Cste for diazotrophs
42   REAL(wp)          :: hratio      = 9.E-5_wp   !: Fe:3He ratio assumed for vent iron supply
43
44   LOGICAL , PUBLIC  :: ll_sbc
45
46   !! * Module variables
47   LOGICAL  ::  ll_solub
48
49   INTEGER , PARAMETER  :: jpriv  = 7   !: Maximum number of river input fields
50   INTEGER , PARAMETER  :: jr_dic = 1   !: index of dissolved inorganic carbon
51   INTEGER , PARAMETER  :: jr_doc = 2   !: index of dissolved organic carbon
52   INTEGER , PARAMETER  :: jr_din = 3   !: index of dissolved inorganic nitrogen
53   INTEGER , PARAMETER  :: jr_don = 4   !: index of dissolved organic nitrogen
54   INTEGER , PARAMETER  :: jr_dip = 5   !: index of dissolved inorganic phosporus
55   INTEGER , PARAMETER  :: jr_dop = 6   !: index of dissolved organic phosphorus
56   INTEGER , PARAMETER  :: jr_dsi = 7   !: index of dissolved silicate
57
58
59   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_dust      ! structure of input dust
60   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub      ! structure of input dust
61   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river  ! structure of input riverdic
62   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ndepo     ! structure of input nitrogen deposition
63   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ironsed   ! structure of input iron from sediment
64   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_hydrofe   ! structure of input iron from hydrothermal vents
65
66   INTEGER , PARAMETER :: nbtimes = 365  !: maximum number of times record in a file
67   INTEGER  :: ntimes_dust, ntimes_riv, ntimes_ndep       ! number of time steps in a file
68   INTEGER  :: ntimes_solub, ntimes_hydro                 ! number of time steps in a file
69
70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: dust, solub       !: dust fields
71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdic, rivalk    !: river input fields
72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdin, rivdip    !: river input fields
73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdsi    !: river input fields
74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: nitdep    !: atmospheric N deposition
75   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ironsed   !: Coastal supply of iron
76   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hydrofe   !: Hydrothermal vent supply of iron
77
78   REAL(wp), PUBLIC :: sumdepsi, rivalkinput, rivdicinput, nitdepinput
79   REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput
80
81   REAL(wp) :: ryyss                    !: number of seconds per year
82
83   !!* Substitution
84#  include "top_substitute.h90"
85   !!----------------------------------------------------------------------
86   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
87   !! $Header:$
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            dust(:,:) = sf_dust(1)%fnow(:,:,1)
120         ENDIF
121      ENDIF
122
123      IF( ll_solub ) THEN
124         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_solub > 1 ) ) THEN
125            CALL fld_read( kt, 1, sf_solub )
126            solub(:,:) = sf_solub(1)%fnow(:,:,1)
127         ENDIF
128      ENDIF
129
130      ! N/P and Si releases due to coastal rivers
131      ! Compute river at nit000 or only if there is more than 1 time record in river file
132      ! -----------------------------------------
133      IF( ln_river ) THEN
134         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_riv > 1 ) ) THEN
135            CALL fld_read( kt, 1, sf_river )
136            DO jj = 1, jpj
137               DO ji = 1, jpi
138                  zcoef = ryyss * cvol(ji,jj,1) 
139                  rivalk(ji,jj) =   sf_river(jr_dic)%fnow(ji,jj,1)                                    &
140                     &              * 1.E3        / ( 12. * zcoef + rtrn )
141                  rivdic(ji,jj) = ( sf_river(jr_dic)%fnow(ji,jj,1) + sf_river(jr_doc)%fnow(ji,jj,1) ) &
142                     &              * 1.E3         / ( 12. * zcoef + rtrn )
143                  rivdin(ji,jj) = ( sf_river(jr_din)%fnow(ji,jj,1) + sf_river(jr_don)%fnow(ji,jj,1) ) &
144                     &              * 1.E3 / rno3 / ( 14. * zcoef + rtrn )
145                  rivdip(ji,jj) = ( sf_river(jr_dip)%fnow(ji,jj,1) + sf_river(jr_dop)%fnow(ji,jj,1) ) &
146                     &              * 1.E3 / po4r / ( 31. * zcoef + rtrn )
147                  rivdsi(ji,jj) =   sf_river(jr_dsi)%fnow(ji,jj,1)                                    &
148                     &              * 1.E3        / ( 28. * zcoef + rtrn )
149               END DO
150            END DO
151         ENDIF
152      ENDIF
153
154      ! Compute N deposition at nit000 or only if there is more than 1 time record in N deposition file
155      IF( ln_ndepo ) THEN
156         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_ndep > 1 ) ) THEN
157            CALL fld_read( kt, 1, sf_ndepo )
158            DO jj = 1, jpj
159               DO ji = 1, jpi
160                  nitdep(ji,jj) = sf_ndepo(1)%fnow(ji,jj,1) / rno3 / ( 14E6 * ryyss * fse3t(ji,jj,1) + rtrn )
161               END DO
162            END DO
163         ENDIF
164      ENDIF
165      !
166      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc')
167      !
168   END SUBROUTINE p4z_sbc
169
170   SUBROUTINE p4z_sbc_init
171
172      !!----------------------------------------------------------------------
173      !!                  ***  routine p4z_sbc_init  ***
174      !!
175      !! ** purpose :   initialization of the external sources of nutrients
176      !!
177      !! ** method  :   read the files and compute the budget
178      !!                called at the first timestep (nittrc000)
179      !!
180      !! ** input   :   external netcdf files
181      !!
182      !!----------------------------------------------------------------------
183      !
184      INTEGER  :: ji, jj, jk, jm, ifpr
185      INTEGER  :: ii0, ii1, ij0, ij1
186      INTEGER  :: numdust, numsolub, numriv, numiron, numdepo, numhydro
187      INTEGER  :: ierr, ierr1, ierr2, ierr3
188      REAL(wp) :: zexpide, zdenitide, zmaskt
189      REAL(wp) :: ztimes_dust, ztimes_riv, ztimes_ndep 
190      REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records
191      REAL(wp), DIMENSION(:), ALLOCATABLE :: rivinput
192      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zdust, zndepo, zriver, zcmask
193      !
194      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
195      TYPE(FLD_N), DIMENSION(jpriv) ::  slf_river    ! array of namelist informations on the fields to read
196      TYPE(FLD_N) ::   sn_dust, sn_solub, sn_ndepo, sn_ironsed, sn_hydrofe   ! informations about the fields to be read
197      TYPE(FLD_N) ::   sn_riverdoc, sn_riverdic, sn_riverdsi   ! informations about the fields to be read
198      TYPE(FLD_N) ::   sn_riverdin, sn_riverdon, sn_riverdip, sn_riverdop
199      !
200      NAMELIST/nampissbc/cn_dir, sn_dust, sn_solub, sn_riverdic, sn_riverdoc, sn_riverdin, sn_riverdon,     &
201        &                sn_riverdip, sn_riverdop, sn_riverdsi, sn_ndepo, sn_ironsed, sn_hydrofe, &
202        &                ln_dust, ln_solub, ln_river, ln_ndepo, ln_ironsed, ln_ironice, ln_hydrofe,    &
203        &                sedfeinput, dustsolub, icefeinput, wdust, nitrfix, diazolight, concfediaz, hratio
204      !!----------------------------------------------------------------------
205      !
206      IF( nn_timing == 1 )  CALL timing_start('p4z_sbc_init')
207      !
208      ryyss   = nyear_len(1) * rday    ! number of seconds per year and per month
209      !
210      !                            !* set file information
211      cn_dir  = './'            ! directory in which the model is executed
212      ! ... default values (NB: frequency positive => hours, negative => months)
213      !                  !   file       ! frequency !  variable   ! time intep !  clim   ! 'yearly' or ! weights  ! rotation   !
214      !                  !   name       !  (hours)  !   name      !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs      !
215      sn_dust     = FLD_N( 'dust'       ,    -1     ,  'dust'     ,  .true.    , .true.  ,   'yearly'  , ''       , ''         )
216      sn_solub    = FLD_N( 'solubility' ,    -12    ,  'solub'    ,  .true.    , .true.  ,   'yearly'  , ''       , ''         )
217      sn_riverdic = FLD_N( 'river'      ,   -12     ,  'riverdic' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
218      sn_riverdoc = FLD_N( 'river'      ,   -12     ,  'riverdoc' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
219      sn_riverdin = FLD_N( 'river'      ,   -12     ,  'riverdin' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
220      sn_riverdon = FLD_N( 'river'      ,   -12     ,  'riverdon' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
221      sn_riverdip = FLD_N( 'river'      ,   -12     ,  'riverdip' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
222      sn_riverdop = FLD_N( 'river'      ,   -12     ,  'riverdop' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
223      sn_riverdsi = FLD_N( 'river'      ,   -12     ,  'riverdsi' ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
224      sn_ndepo    = FLD_N( 'ndeposition',   -12     ,  'ndep'     ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
225      sn_ironsed  = FLD_N( 'ironsed'    ,   -12     ,  'bathy'    ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
226      sn_hydrofe  = FLD_N( 'hydrofe'    ,   -12     ,  'hydro'    ,  .false.   , .true.  ,   'yearly'  , ''       , ''         )
227
228      REWIND( numnatp )                     ! read numnatp
229      READ  ( numnatp, nampissbc )
230
231      IF(lwp) THEN
232         WRITE(numout,*) ' '
233         WRITE(numout,*) ' namelist : nampissbc '
234         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ '
235         WRITE(numout,*) '    dust input from the atmosphere           ln_dust     = ', ln_dust
236         WRITE(numout,*) '    Variable solubility of iron input        ln_solub    = ', ln_solub
237         WRITE(numout,*) '    river input of nutrients                 ln_river    = ', ln_river
238         WRITE(numout,*) '    atmospheric deposition of n              ln_ndepo    = ', ln_ndepo
239         WRITE(numout,*) '    Fe input from sediments                  ln_ironsed  = ', ln_ironsed
240         WRITE(numout,*) '    Fe input from seaice                     ln_ironice  = ', ln_ironice
241         WRITE(numout,*) '    fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe
242         WRITE(numout,*) '    coastal release of iron                  sedfeinput  = ', sedfeinput
243         WRITE(numout,*) '    solubility of the dust                   dustsolub   = ', dustsolub
244         WRITE(numout,*) '    Iron concentration in sea ice            icefeinput  = ', icefeinput
245         WRITE(numout,*) '    sinking speed of the dust                wdust       = ', wdust
246         WRITE(numout,*) '    nitrogen fixation rate                   nitrfix     = ', nitrfix
247         WRITE(numout,*) '    nitrogen fixation sensitivty to light    diazolight  = ', diazolight
248         WRITE(numout,*) '    fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz
249         WRITE(numout,*) '    Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio
250      END IF
251
252      IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN  ;  ll_sbc = .TRUE.
253      ELSE                                            ;  ll_sbc = .FALSE.
254      ENDIF
255
256      IF( ln_dust .AND. ln_solub ) THEN               ;  ll_solub = .TRUE.
257      ELSE                                            ;  ll_solub = .FALSE.
258      ENDIF
259
260      ! dust input from the atmosphere
261      ! ------------------------------
262      IF( ln_dust ) THEN 
263         !
264         IF(lwp) WRITE(numout,*) '    initialize dust input from atmosphere '
265         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
266         !
267         ALLOCATE( dust(jpi,jpj) )    ! allocation
268         !
269         ALLOCATE( sf_dust(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
270         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_dust structure' )
271         !
272         CALL fld_fill( sf_dust, (/ sn_dust /), cn_dir, 'p4z_sed_init', 'Atmospheric dust deposition', 'nampissed' )
273                                   ALLOCATE( sf_dust(1)%fnow(jpi,jpj,1)   )
274         IF( sn_dust%ln_tint )     ALLOCATE( sf_dust(1)%fdta(jpi,jpj,1,2) )
275         !
276         ! Get total input dust ; need to compute total atmospheric supply of Si in a year
277         CALL iom_open (  TRIM( sn_dust%clname ) , numdust )
278         CALL iom_gettime( numdust, zsteps, kntime=ntimes_dust)  ! get number of record in file
279         ALLOCATE( zdust(jpi,jpj,ntimes_dust) )
280         DO jm = 1, ntimes_dust
281            CALL iom_get( numdust, jpdom_data, TRIM( sn_dust%clvar ), zdust(:,:,jm), jm )
282         END DO
283         CALL iom_close( numdust )
284         ztimes_dust = 1._wp / FLOAT( ntimes_dust ) 
285         sumdepsi = 0.e0
286         DO jm = 1, ntimes_dust
287            sumdepsi = sumdepsi + glob_sum( zdust(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_dust )
288         ENDDO
289         sumdepsi = sumdepsi / ( nyear_len(1) * rday ) * 12. * 8.8 * 0.075 / 28.1 
290         DEALLOCATE( zdust)
291      ELSE
292         sumdepsi  = 0._wp
293      END IF
294
295      ! Solubility of dust deposition of iron
296      ! Only if ln_dust and ln_solubility set to true (ll_solub = .true.)
297      ! -----------------------------------------------------------------
298      IF( ll_solub ) THEN
299         !
300         IF(lwp) WRITE(numout,*) '    initialize variable solubility of Fe '
301         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
302         !
303         ALLOCATE( solub(jpi,jpj) )    ! allocation
304         !
305         ALLOCATE( sf_solub(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst
306         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_solub structure' )
307         !
308         CALL fld_fill( sf_solub, (/ sn_solub /), cn_dir, 'p4z_sed_init', 'Solubility of atm. iron ', 'nampissed' )
309                                   ALLOCATE( sf_solub(1)%fnow(jpi,jpj,1)   )
310         IF( sn_solub%ln_tint )    ALLOCATE( sf_solub(1)%fdta(jpi,jpj,1,2) )
311         ! get number of record in file
312         CALL iom_open (  TRIM( sn_solub%clname ) , numsolub )
313         CALL iom_gettime( numsolub, zsteps, kntime=ntimes_solub)  ! get number of record in file
314         CALL iom_close( numsolub )
315      ENDIF
316
317      ! nutrient input from rivers
318      ! --------------------------
319      IF( ln_river ) THEN
320         !
321         slf_river(jr_dic) = sn_riverdic  ;  slf_river(jr_doc) = sn_riverdoc  ;  slf_river(jr_din) = sn_riverdin 
322         slf_river(jr_don) = sn_riverdon  ;  slf_river(jr_dip) = sn_riverdip  ;  slf_river(jr_dop) = sn_riverdop
323         slf_river(jr_dsi) = sn_riverdsi 
324         !
325         ALLOCATE( rivdic(jpi,jpj), rivalk(jpi,jpj), rivdin(jpi,jpj), rivdip(jpi,jpj), rivdsi(jpi,jpj) ) 
326         !
327         ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )           !* allocate and fill sf_sst (forcing structure) with sn_sst
328         rivinput(:) = 0.0
329
330         IF( ierr1 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_irver structure' )
331         !
332         CALL fld_fill( sf_river, slf_river, cn_dir, 'p4z_sed_init', 'Input from river ', 'nampissed' )
333         DO ifpr = 1, jpriv
334                                          ALLOCATE( sf_river(ifpr)%fnow(jpi,jpj,1  ) )
335            IF( slf_river(ifpr)%ln_tint ) ALLOCATE( sf_river(ifpr)%fdta(jpi,jpj,1,2) )
336         END DO
337         ! Get total input rivers ; need to compute total river supply in a year
338         DO ifpr = 1, jpriv
339            CALL iom_open ( TRIM( slf_river(ifpr)%clname ), numriv )
340            CALL iom_gettime( numriv, zsteps, kntime=ntimes_riv)
341            ALLOCATE( zriver(jpi,jpj,ntimes_riv) )
342            DO jm = 1, ntimes_riv
343               CALL iom_get( numriv, jpdom_data, TRIM( slf_river(ifpr)%clvar ), zriver(:,:,jm), jm )
344            END DO
345            CALL iom_close( numriv )
346            ztimes_riv = 1._wp / FLOAT(ntimes_riv) 
347            DO jm = 1, ntimes_riv
348               rivinput(ifpr) = rivinput(ifpr) + glob_sum( zriver(:,:,jm) * tmask(:,:,1) * ztimes_riv ) 
349            END DO
350            DEALLOCATE( zriver)
351         END DO
352         ! N/P and Si releases due to coastal rivers
353         ! -----------------------------------------
354         rivdicinput = (rivinput(jr_dic) + rivinput(jr_doc) ) * 1E3 / 12._wp
355         rivdininput = (rivinput(jr_din) + rivinput(jr_don) ) * 1E3 / rno3 / 14._wp
356         rivdipinput = (rivinput(jr_dip) + rivinput(jr_dop) ) * 1E3 / po4r / 31._wp
357         rivdsiinput = rivinput(jr_dsi) * 1E3 / 28._wp
358         rivalkinput = rivinput(jr_dic) * 1E3 / 12._wp
359         !
360      ELSE
361         rivdicinput = 0._wp
362         rivdininput = 0._wp
363         rivdipinput = 0._wp
364         rivdsiinput = 0._wp
365         rivalkinput = 0._wp
366      END IF 
367
368      ! nutrient input from dust
369      ! ------------------------
370      IF( ln_ndepo ) THEN
371         !
372         IF(lwp) WRITE(numout,*) '    initialize the nutrient input by dust from ndeposition.orca.nc'
373         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
374         !
375         ALLOCATE( nitdep(jpi,jpj) )    ! allocation
376         !
377         ALLOCATE( sf_ndepo(1), STAT=ierr3 )           !* allocate and fill sf_sst (forcing structure) with sn_sst
378         IF( ierr3 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_ndepo structure' )
379         !
380         CALL fld_fill( sf_ndepo, (/ sn_ndepo /), cn_dir, 'p4z_sed_init', 'Nutrient atmospheric depositon ', 'nampissed' )
381                                   ALLOCATE( sf_ndepo(1)%fnow(jpi,jpj,1)   )
382         IF( sn_ndepo%ln_tint )    ALLOCATE( sf_ndepo(1)%fdta(jpi,jpj,1,2) )
383         !
384         ! Get total input dust ; need to compute total atmospheric supply of N in a year
385         CALL iom_open ( TRIM( sn_ndepo%clname ), numdepo )
386         CALL iom_gettime( numdepo, zsteps, kntime=ntimes_ndep)
387         ALLOCATE( zndepo(jpi,jpj,ntimes_ndep) )
388         DO jm = 1, ntimes_ndep
389            CALL iom_get( numdepo, jpdom_data, TRIM( sn_ndepo%clvar ), zndepo(:,:,jm), jm )
390         END DO
391         CALL iom_close( numdepo )
392         ztimes_ndep = 1._wp / FLOAT( ntimes_ndep ) 
393         nitdepinput = 0._wp
394         DO jm = 1, ntimes_ndep
395           nitdepinput = nitdepinput + glob_sum( zndepo(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_ndep )
396         ENDDO
397         nitdepinput = nitdepinput / rno3 / 14E6 
398         DEALLOCATE( zndepo)
399      ELSE
400         nitdepinput = 0._wp
401      ENDIF
402
403      ! coastal and island masks
404      ! ------------------------
405      IF( ln_ironsed ) THEN     
406         !
407         IF(lwp) WRITE(numout,*) '    computation of an island mask to enhance coastal supply of iron'
408         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
409         !
410         ALLOCATE( ironsed(jpi,jpj,jpk) )    ! allocation
411         !
412         CALL iom_open ( TRIM( sn_ironsed%clname ), numiron )
413         ALLOCATE( zcmask(jpi,jpj,jpk) )
414         CALL iom_get  ( numiron, jpdom_data, TRIM( sn_ironsed%clvar ), zcmask(:,:,:), 1 )
415         CALL iom_close( numiron )
416         !
417         DO jk = 1, 5
418            DO jj = 2, jpjm1
419               DO ji = fs_2, fs_jpim1
420                  IF( tmask(ji,jj,jk) /= 0. ) THEN
421                     zmaskt = tmask(ji+1,jj,jk) * tmask(ji-1,jj,jk) * tmask(ji,jj+1,jk)    &
422                        &                       * tmask(ji,jj-1,jk) * tmask(ji,jj,jk+1)
423                     IF( zmaskt == 0. )   zcmask(ji,jj,jk ) = MAX( 0.1, zcmask(ji,jj,jk) ) 
424                  END IF
425               END DO
426            END DO
427         END DO
428         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 ) THEN
429            ii0 = 176   ;   ii1 =  176        ! Southern Island : Kerguelen
430            ij0 =  37   ;   ij1 =   37  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
431            !
432            ii0 = 119   ;   ii1 =  119        ! South Georgia
433            ij0 =  29   ;   ij1 =   29  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
434            !
435            ii0 = 111   ;   ii1 =  111        ! Falklands
436            ij0 =  35   ;   ij1 =   35  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
437            !
438            ii0 = 168   ;   ii1 =  168        ! Crozet
439            ij0 =  40   ;   ij1 =   40  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
440            !
441            ii0 = 119   ;   ii1 =  119        ! South Orkney
442            ij0 =  28   ;   ij1 =   28  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
443            !
444            ii0 = 140   ;   ii1 =  140        ! Bouvet Island
445            ij0 =  33   ;   ij1 =   33  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
446            !
447            ii0 = 178   ;   ii1 =  178        ! Prince edwards
448            ij0 =  34   ;   ij1 =   34  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
449            !
450            ii0 =  43   ;   ii1 =   43        ! Balleny islands
451            ij0 =  21   ;   ij1 =   21  ;   zcmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1), 1:jpk ) =  0.3_wp 
452         ENDIF
453         CALL lbc_lnk( zcmask , 'T', 1. )      ! lateral boundary conditions on cmask   (sign unchanged)
454         DO jk = 1, jpk
455            DO jj = 1, jpj
456               DO ji = 1, jpi
457                  zexpide   = MIN( 8.,( fsdept(ji,jj,jk) / 500. )**(-1.5) )
458                  zdenitide = -0.9543 + 0.7662 * LOG( zexpide ) - 0.235 * LOG( zexpide )**2
459                  zcmask(ji,jj,jk) = zcmask(ji,jj,jk) * MIN( 1., EXP( zdenitide ) / 0.5 )
460               END DO
461            END DO
462         END DO
463         ! Coastal supply of iron
464         ! -------------------------
465         ironsed(:,:,jpk) = 0._wp
466         DO jk = 1, jpkm1
467            ironsed(:,:,jk) = sedfeinput * zcmask(:,:,jk) / ( fse3t(:,:,jk) * rday )
468         END DO
469         DEALLOCATE( zcmask)
470      ENDIF
471      !
472      ! Iron from Hydrothermal vents
473      ! ------------------------
474      IF( ln_hydrofe ) THEN
475         !
476         IF(lwp) WRITE(numout,*) '    Input of iron from hydrothermal vents '
477         IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
478         !
479         ALLOCATE( hydrofe(jpi,jpj,jpk) )    ! allocation
480         !
481         CALL iom_open ( TRIM( sn_hydrofe%clname ), numhydro )
482         CALL iom_get  ( numhydro, jpdom_data, TRIM( sn_hydrofe%clvar ), hydrofe(:,:,:), 1 )
483         CALL iom_close( numhydro )
484         !
485         hydrofe(:,:,:) = ( hydrofe(:,:,:) * hratio ) / ( cvol(:,:,:) * ryyss + rtrn ) / fse3t(:,:,:)
486         !
487      ENDIF
488      !
489      IF( ll_sbc ) CALL p4z_sbc( nit000 ) 
490      !
491      IF(lwp) THEN
492         WRITE(numout,*)
493         WRITE(numout,*) '    Total input of elements from river supply'
494         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
495         WRITE(numout,*) '    N Supply   : ', rivdininput*rno3*1E3/1E12*14.,' TgN/yr'
496         WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.,' TgSi/yr'
497         WRITE(numout,*) '    P Supply   : ', rivdipinput*1E3*po4r/1E12*31.,' TgP/yr'
498         WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12,' Teq/yr'
499         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12,'TgC/yr'
500         WRITE(numout,*) 
501         WRITE(numout,*) '    Total input of elements from atmospheric supply'
502         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
503         WRITE(numout,*) '    N Supply   : ', nitdepinput*rno3*1E3/1E12*14.,' TgN/yr'
504         WRITE(numout,*) 
505      ENDIF
506      !
507      IF( nn_timing == 1 )  CALL timing_stop('p4z_sbc_init')
508      !
509   END SUBROUTINE p4z_sbc_init
510
511#else
512   !!======================================================================
513   !!  Dummy module :                                   No PISCES bio-model
514   !!======================================================================
515CONTAINS
516   SUBROUTINE p4z_sbc                         ! Empty routine
517   END SUBROUTINE p4z_sbc
518#endif 
519
520   !!======================================================================
521END MODULE  p4zsbc
Note: See TracBrowser for help on using the repository browser.