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.
Changeset 5266 for branches/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 – NEMO

Ignore:
Timestamp:
2015-05-13T10:37:43+02:00 (9 years ago)
Author:
cetlod
Message:

PISCES_QUOTA : First commits, see ticket #1516

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r4521 r5266  
    1111   !!             3.5  !  2012-05  (C. Ethe) Merge PISCES-LOBSTER 
    1212   !!---------------------------------------------------------------------- 
    13 #if defined key_pisces || defined key_pisces_reduced 
     13#if defined key_pisces || defined key_pisces_reduced || defined key_pisces_quota 
    1414   !!---------------------------------------------------------------------- 
    1515   !!   'key_pisces'                                       PISCES bio-model 
     
    4343      !!---------------------------------------------------------------------- 
    4444 
    45       IF( lk_p4z ) THEN  ;   CALL p4z_ini   !  PISCES 
    46       ELSE               ;   CALL p2z_ini   !  LOBSTER 
    47       ENDIF 
     45      SELECT CASE ( nn_p4z ) 
     46      ! 
     47        CASE(1)          ;   CALL p2z_ini   !  LOBSTER 
     48        CASE(2)          ;   CALL p4z_ini   !  PISCES 
     49        CASE(3)          ;   CALL p5z_ini   !  PISCES QUOTA 
     50 
     51      END SELECT 
    4852 
    4953   END SUBROUTINE trc_ini_pisces 
     54 
     55   SUBROUTINE p5z_ini 
     56      !!---------------------------------------------------------------------- 
     57      !!                   ***  ROUTINE p5z_ini *** 
     58      !! 
     59      !! ** Purpose :   Initialisation of the PISCES biochemical model 
     60      !!                with variable stoichiometry 
     61      !!---------------------------------------------------------------------- 
     62#if defined key_pisces_quota  
     63      ! 
     64      USE p5zsms          ! Main P4Z routine 
     65      USE p4zche          !  Chemical model 
     66      USE p5zsink         !  vertical flux of particulate matter due to sinking 
     67      USE p4zopt          !  optical model 
     68      USE p4zsbc          !  Boundary conditions 
     69      USE p4zfechem       !  Iron chemistry 
     70      USE p5zrem          !  Remineralisation of organic matter 
     71      USE p4zflx          !  Gas exchange 
     72      USE p5zlim          !  Co-limitations of differents nutrients 
     73      USE p5zprod         !  Growth rate of the 2 phyto groups 
     74      USE p5zmicro        !  Sources and sinks of microzooplankton 
     75      USE p5zmeso         !  Sources and sinks of mesozooplankton 
     76      USE p5zmort         !  Mortality terms for phytoplankton 
     77      USE p4zlys          !  Calcite saturation 
     78      ! 
     79      REAL(wp), SAVE :: sco2   =  2.312e-3_wp 
     80      REAL(wp), SAVE :: alka0  =  2.423e-3_wp 
     81      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp  
     82      REAL(wp), SAVE :: po4    =  2.174e-6_wp  
     83      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp   
     84      REAL(wp), SAVE :: silic1 =  91.65e-6_wp   
     85      REAL(wp), SAVE :: no3    =  31.04e-6_wp * 7.625_wp 
     86      ! 
     87      INTEGER  ::  ji, jj, jk, ierr 
     88      REAL(wp) ::  zcaralk, zbicarb, zco3 
     89      REAL(wp) ::  ztmas, ztmas1 
     90      !!---------------------------------------------------------------------- 
     91 
     92      IF(lwp) WRITE(numout,*) 
     93      IF(lwp) WRITE(numout,*) ' p5z_ini :   PISCES biochemical model initialisation' 
     94      IF(lwp) WRITE(numout,*) '             With variable stoichiometry' 
     95      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 
     96 
     97                                                 ! Allocate PISCES arrays 
     98      ierr =         sms_pisces_alloc()           
     99      ierr = ierr +  p4z_che_alloc() 
     100      ierr = ierr +  p5z_sink_alloc() 
     101      ierr = ierr +  p4z_opt_alloc() 
     102      ierr = ierr +  p5z_prod_alloc() 
     103      ierr = ierr +  p5z_rem_alloc() 
     104      ierr = ierr +  p4z_flx_alloc() 
     105      ! 
     106      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
     107      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' ) 
     108      ! 
     109      CALL p5z_sms_init       !  Maint routine 
     110      !                                            ! Time-step 
     111      rfact   = rdttrc(1)                          ! --------- 
     112      rfactr  = 1. / rfact 
     113      rfact2  = rfact / FLOAT( nrdttrc ) 
     114      rfact2r = 1. / rfact2 
     115 
     116      IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1) 
     117      IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2 
     118 
     119      ! Set biological ratios 
     120      ! --------------------- 
     121      rno3    =  16._wp / 122._wp 
     122      po4r    =   1._wp / 122._wp 
     123      o2nit   =  32._wp / 122._wp 
     124      rdenit  = 105._wp /  16._wp 
     125      rdenita =   3._wp /  5._wp 
     126      o2ut    = 133._wp / 122._wp 
     127      no3rat3 = no3rat3 / rno3 
     128      po4rat3 = po4rat3 / po4r 
     129 
     130      ! Initialization of tracer concentration in case of  no restart  
     131      !-------------------------------------------------------------- 
     132      IF( .NOT. ln_rsttr ) THEN   
     133          
     134         trn(:,:,:,jpdic) = sco2 
     135         trn(:,:,:,jpdoc) = bioma0 
     136         trn(:,:,:,jpdon) = bioma0 
     137         trn(:,:,:,jpdop) = bioma0 
     138         trn(:,:,:,jptal) = alka0 
     139         trn(:,:,:,jpoxy) = oxyg0 
     140         trn(:,:,:,jpcal) = bioma0 
     141         trn(:,:,:,jppo4) = po4 / po4r 
     142         trn(:,:,:,jppoc) = bioma0 
     143         trn(:,:,:,jppon) = bioma0 
     144         trn(:,:,:,jppop) = bioma0 
     145#  if ! defined key_kriest 
     146         trn(:,:,:,jpgoc) = bioma0 
     147         trn(:,:,:,jpgon) = bioma0 
     148         trn(:,:,:,jpgop) = bioma0 
     149         trn(:,:,:,jpbfe) = bioma0 * 5.e-6 
     150#  else 
     151         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp ) 
     152#  endif 
     153         trn(:,:,:,jpsil) = silic1 
     154         trn(:,:,:,jpdsi) = bioma0 * 0.15 
     155         trn(:,:,:,jpgsi) = bioma0 * 5.e-6 
     156         trn(:,:,:,jpphy) = bioma0 
     157         trn(:,:,:,jpnph) = bioma0 
     158         trn(:,:,:,jppph) = bioma0 
     159         trn(:,:,:,jppic) = bioma0 
     160         trn(:,:,:,jpnpi) = bioma0 
     161         trn(:,:,:,jpppi) = bioma0 
     162         trn(:,:,:,jpdia) = bioma0 
     163         trn(:,:,:,jpndi) = bioma0 
     164         trn(:,:,:,jppdi) = bioma0 
     165         trn(:,:,:,jpzoo) = bioma0 
     166         trn(:,:,:,jpmes) = bioma0 
     167         trn(:,:,:,jpfer) = 0.6E-9 
     168         trn(:,:,:,jpsfe) = bioma0 * 5.e-6 
     169         trn(:,:,:,jppfe) = bioma0 * 5.e-6 
     170         trn(:,:,:,jpdfe) = bioma0 * 5.e-6 
     171         trn(:,:,:,jpnfe) = bioma0 * 5.e-6 
     172         trn(:,:,:,jpnch) = bioma0 * 12. / 55. 
     173         trn(:,:,:,jppch) = bioma0 * 12. / 55. 
     174         trn(:,:,:,jpdch) = bioma0 * 12. / 55. 
     175         trn(:,:,:,jpno3) = no3 
     176         trn(:,:,:,jpnh4) = bioma0 
     177 
     178         ! initialize the half saturation constant for silicate 
     179         ! ---------------------------------------------------- 
     180         xksi(:,:)    = 2.e-6 
     181         xksimax(:,:) = xksi(:,:) 
     182      END IF 
     183 
     184      ! Time step duration for biology 
     185      xstep = rfact2 / rday 
     186 
     187      CALL p5z_sink_init      !  vertical flux of particulate organic matter 
     188      CALL p4z_opt_init       !  Optic: PAR in the water column 
     189      CALL p5z_lim_init       !  co-limitations by the various nutrients 
     190      CALL p5z_prod_init      !  phytoplankton growth rate over the global ocean. 
     191      CALL p4z_sbc_init       !  boundary conditions 
     192      CALL p4z_fechem_init    !  Iron chemistry 
     193      CALL p5z_rem_init       !  remineralisation 
     194      CALL p5z_mort_init      !  phytoplankton mortality  
     195      CALL p5z_micro_init     !  microzooplankton 
     196      CALL p5z_meso_init      !  mesozooplankton 
     197      CALL p4z_lys_init       !  calcite saturation 
     198      CALL p4z_flx_init       !  gas exchange  
     199 
     200      ndayflxtr = 0 
     201 
     202      IF(lwp) WRITE(numout,*)  
     203      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done' 
     204      IF(lwp) WRITE(numout,*)  
     205#endif 
     206      ! 
     207   END SUBROUTINE p5z_ini 
    50208 
    51209   SUBROUTINE p4z_ini 
     
    74232      REAL(wp), SAVE :: sco2   =  2.312e-3_wp 
    75233      REAL(wp), SAVE :: alka0  =  2.423e-3_wp 
    76       REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp  
    77       REAL(wp), SAVE :: po4    =  2.174e-6_wp  
    78       REAL(wp), SAVE :: bioma0 =  1.000e-8_wp   
    79       REAL(wp), SAVE :: silic1 =  91.65e-6_wp   
     234      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp 
     235      REAL(wp), SAVE :: po4    =  2.174e-6_wp 
     236      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp 
     237      REAL(wp), SAVE :: silic1 =  91.65e-6_wp 
    80238      REAL(wp), SAVE :: no3    =  31.04e-6_wp * 7.625_wp 
    81239      ! 
     
    90248 
    91249                                                 ! Allocate PISCES arrays 
    92       ierr =         sms_pisces_alloc()           
     250      ierr =         sms_pisces_alloc() 
    93251      ierr = ierr +  p4z_che_alloc() 
    94252      ierr = ierr +  p4z_sink_alloc() 
     
    125283      ! Initialization of tracer concentration in case of  no restart  
    126284      !-------------------------------------------------------------- 
    127       IF( .NOT. ln_rsttr ) THEN   
    128           
     285      IF( .NOT. ln_rsttr ) THEN 
     286 
    129287         trn(:,:,:,jpdic) = sco2 
    130288         trn(:,:,:,jpdoc) = bioma0 
     
    180338      ndayflxtr = 0 
    181339 
    182       IF(lwp) WRITE(numout,*)  
     340      IF(lwp) WRITE(numout,*) 
    183341      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done' 
    184       IF(lwp) WRITE(numout,*)  
     342      IF(lwp) WRITE(numout,*) 
    185343#endif 
    186344      ! 
Note: See TracChangeset for help on using the changeset viewer.