trcini_pisces.F90 9.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244
  1. MODULE trcini_pisces
  2. !!======================================================================
  3. !! *** MODULE trcini_pisces ***
  4. !! TOP : initialisation of the PISCES biochemical model
  5. !!======================================================================
  6. !! History : - ! 1988-07 (E. Maier-Reiner) Original code
  7. !! - ! 1999-10 (O. Aumont, C. Le Quere)
  8. !! - ! 2002 (O. Aumont) PISCES
  9. !! 1.0 ! 2005-03 (O. Aumont, A. El Moussaoui) F90
  10. !! 2.0 ! 2007-12 (C. Ethe, G. Madec) from trcini.pisces.h90
  11. !! 3.5 ! 2012-05 (C. Ethe) Merge PISCES-LOBSTER
  12. !!----------------------------------------------------------------------
  13. #if defined key_pisces || defined key_pisces_reduced
  14. !!----------------------------------------------------------------------
  15. !! 'key_pisces' PISCES bio-model
  16. !!----------------------------------------------------------------------
  17. !! trc_ini_pisces : PISCES biochemical model initialisation
  18. !!----------------------------------------------------------------------
  19. USE par_trc ! TOP parameters
  20. USE oce_trc ! shared variables between ocean and passive tracers
  21. USE trc ! passive tracers common variables
  22. USE sms_pisces ! PISCES Source Minus Sink variables
  23. IMPLICIT NONE
  24. PRIVATE
  25. PUBLIC trc_ini_pisces ! called by trcini.F90 module
  26. # include "top_substitute.h90"
  27. !!----------------------------------------------------------------------
  28. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  29. !! $Id: trcini_pisces.F90 4521 2014-03-03 18:12:24Z cetlod $
  30. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  31. !!----------------------------------------------------------------------
  32. CONTAINS
  33. SUBROUTINE trc_ini_pisces
  34. !!----------------------------------------------------------------------
  35. !! *** ROUTINE trc_ini_pisces ***
  36. !!
  37. !! ** Purpose : Initialisation of the PISCES biochemical model
  38. !!----------------------------------------------------------------------
  39. IF( lk_p4z ) THEN ; CALL p4z_ini ! PISCES
  40. ELSE ; CALL p2z_ini ! LOBSTER
  41. ENDIF
  42. END SUBROUTINE trc_ini_pisces
  43. SUBROUTINE p4z_ini
  44. !!----------------------------------------------------------------------
  45. !! *** ROUTINE p4z_ini ***
  46. !!
  47. !! ** Purpose : Initialisation of the PISCES biochemical model
  48. !!----------------------------------------------------------------------
  49. #if defined key_pisces
  50. !
  51. USE p4zsms ! Main P4Z routine
  52. USE p4zche ! Chemical model
  53. USE p4zsink ! vertical flux of particulate matter due to sinking
  54. USE p4zopt ! optical model
  55. USE p4zsbc ! Boundary conditions
  56. USE p4zfechem ! Iron chemistry
  57. USE p4zrem ! Remineralisation of organic matter
  58. USE p4zflx ! Gas exchange
  59. USE p4zlim ! Co-limitations of differents nutrients
  60. USE p4zprod ! Growth rate of the 2 phyto groups
  61. USE p4zmicro ! Sources and sinks of microzooplankton
  62. USE p4zmeso ! Sources and sinks of mesozooplankton
  63. USE p4zmort ! Mortality terms for phytoplankton
  64. USE p4zlys ! Calcite saturation
  65. USE p4zsed ! Sedimentation & burial
  66. !
  67. REAL(wp), SAVE :: sco2 = 2.312e-3_wp
  68. REAL(wp), SAVE :: alka0 = 2.426e-3_wp
  69. REAL(wp), SAVE :: oxyg0 = 177.6e-6_wp
  70. REAL(wp), SAVE :: po4 = 2.165e-6_wp
  71. REAL(wp), SAVE :: bioma0 = 1.000e-8_wp
  72. REAL(wp), SAVE :: silic1 = 91.51e-6_wp
  73. REAL(wp), SAVE :: no3 = 30.9e-6_wp * 7.625_wp
  74. !
  75. INTEGER :: ji, jj, jk, ierr
  76. REAL(wp) :: zcaralk, zbicarb, zco3
  77. REAL(wp) :: ztmas, ztmas1
  78. !!----------------------------------------------------------------------
  79. IF(lwp) WRITE(numout,*)
  80. IF(lwp) WRITE(numout,*) ' p4z_ini : PISCES biochemical model initialisation'
  81. IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
  82. ! Allocate PISCES arrays
  83. ierr = sms_pisces_alloc()
  84. ierr = ierr + p4z_che_alloc()
  85. ierr = ierr + p4z_sink_alloc()
  86. ierr = ierr + p4z_opt_alloc()
  87. ierr = ierr + p4z_prod_alloc()
  88. ierr = ierr + p4z_rem_alloc()
  89. ierr = ierr + p4z_flx_alloc()
  90. ierr = ierr + p4z_sed_alloc()
  91. !
  92. IF( lk_mpp ) CALL mpp_sum( ierr )
  93. IF( ierr /= 0 ) CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' )
  94. !
  95. ryyss = nyear_len(1) * rday ! number of seconds per year
  96. r1_ryyss = 1. / ryyss
  97. !
  98. CALL p4z_sms_init ! Maint routine
  99. ! ! Time-step
  100. ! Set biological ratios
  101. ! ---------------------
  102. rno3 = 16._wp / 122._wp
  103. po4r = 1._wp / 122._wp
  104. o2nit = 32._wp / 122._wp
  105. o2ut = 133._wp / 122._wp
  106. rdenit = ( ( o2ut + o2nit ) * 0.80 - rno3 - rno3 * 0.60 ) / rno3
  107. rdenita = 3._wp / 5._wp
  108. ! Initialization of tracer concentration in case of no restart
  109. !--------------------------------------------------------------
  110. IF( .NOT. ln_rsttr ) THEN
  111. trn(:,:,:,jpdic) = sco2
  112. trn(:,:,:,jpdoc) = bioma0
  113. trn(:,:,:,jptal) = alka0
  114. trn(:,:,:,jpoxy) = oxyg0
  115. trn(:,:,:,jpcal) = bioma0
  116. trn(:,:,:,jppo4) = po4 / po4r
  117. trn(:,:,:,jppoc) = bioma0
  118. # if ! defined key_kriest
  119. trn(:,:,:,jpgoc) = bioma0
  120. trn(:,:,:,jpbfe) = bioma0 * 5.e-6
  121. # else
  122. trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
  123. # endif
  124. trn(:,:,:,jpsil) = silic1
  125. trn(:,:,:,jpdsi) = bioma0 * 0.15
  126. trn(:,:,:,jpgsi) = bioma0 * 5.e-6
  127. trn(:,:,:,jpphy) = bioma0
  128. trn(:,:,:,jpdia) = bioma0
  129. trn(:,:,:,jpzoo) = bioma0
  130. trn(:,:,:,jpmes) = bioma0
  131. trn(:,:,:,jpfer) = 0.6E-9
  132. trn(:,:,:,jpsfe) = bioma0 * 5.e-6
  133. trn(:,:,:,jpdfe) = bioma0 * 5.e-6
  134. trn(:,:,:,jpnfe) = bioma0 * 5.e-6
  135. trn(:,:,:,jpnch) = bioma0 * 12. / 55.
  136. trn(:,:,:,jpdch) = bioma0 * 12. / 55.
  137. trn(:,:,:,jpno3) = no3
  138. trn(:,:,:,jpnh4) = bioma0
  139. ! initialize the half saturation constant for silicate
  140. ! ----------------------------------------------------
  141. xksi(:,:) = 2.e-6
  142. xksimax(:,:) = xksi(:,:)
  143. END IF
  144. CALL p4z_sink_init ! vertical flux of particulate organic matter
  145. CALL p4z_opt_init ! Optic: PAR in the water column
  146. CALL p4z_lim_init ! co-limitations by the various nutrients
  147. CALL p4z_prod_init ! phytoplankton growth rate over the global ocean.
  148. CALL p4z_sbc_init ! boundary conditions
  149. CALL p4z_fechem_init ! Iron chemistry
  150. CALL p4z_rem_init ! remineralisation
  151. CALL p4z_mort_init ! phytoplankton mortality
  152. CALL p4z_micro_init ! microzooplankton
  153. CALL p4z_meso_init ! mesozooplankton
  154. CALL p4z_lys_init ! calcite saturation
  155. CALL p4z_flx_init ! gas exchange
  156. ndayflxtr = 0
  157. IF(lwp) WRITE(numout,*)
  158. IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
  159. IF(lwp) WRITE(numout,*)
  160. #endif
  161. !
  162. END SUBROUTINE p4z_ini
  163. SUBROUTINE p2z_ini
  164. !!----------------------------------------------------------------------
  165. !! *** ROUTINE p2z_ini ***
  166. !!
  167. !! ** Purpose : Initialisation of the LOBSTER biochemical model
  168. !!----------------------------------------------------------------------
  169. #if defined key_pisces_reduced
  170. !
  171. USE p2zopt
  172. USE p2zexp
  173. USE p2zbio
  174. USE p2zsed
  175. !
  176. INTEGER :: ji, jj, jk, ierr
  177. !!----------------------------------------------------------------------
  178. IF(lwp) WRITE(numout,*)
  179. IF(lwp) WRITE(numout,*) ' p2z_ini : LOBSTER biochemical model initialisation'
  180. IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
  181. ierr = sms_pisces_alloc()
  182. ierr = ierr + p2z_exp_alloc()
  183. !
  184. IF( lk_mpp ) CALL mpp_sum( ierr )
  185. IF( ierr /= 0 ) CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' )
  186. ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07
  187. ! ----------------------
  188. IF( .NOT. ln_rsttr ) THEN ! in case of no restart
  189. trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:)
  190. trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:)
  191. trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:)
  192. trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:)
  193. trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:)
  194. WHERE( rhd(:,:,:) <= 24.5e-3 ) ; trn(:,:,:,jpno3 ) = 2._wp * tmask(:,:,:)
  195. ELSE WHERE ; trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:)
  196. END WHERE
  197. ENDIF
  198. ! ! Namelist read
  199. CALL p2z_opt_init ! Optics parameters
  200. CALL p2z_sed_init ! sedimentation
  201. CALL p2z_bio_init ! biology
  202. CALL p2z_exp_init ! export
  203. !
  204. IF(lwp) WRITE(numout,*)
  205. IF(lwp) WRITE(numout,*) 'Initialization of LOBSTER tracers done'
  206. IF(lwp) WRITE(numout,*)
  207. #endif
  208. !
  209. END SUBROUTINE p2z_ini
  210. #else
  211. !!----------------------------------------------------------------------
  212. !! Dummy module No PISCES biochemical model
  213. !!----------------------------------------------------------------------
  214. CONTAINS
  215. SUBROUTINE trc_ini_pisces ! Empty routine
  216. END SUBROUTINE trc_ini_pisces
  217. #endif
  218. !!======================================================================
  219. END MODULE trcini_pisces