p4zsbc.F90 24 KB

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