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 2528 for trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90

    • Property svn:executable deleted
    r1753 r2528  
    2222   USE p4zche          !  
    2323   USE p4zbio          !  
     24   USE p4zsink         !  
     25   USE p4zopt          !  
     26   USE p4zlim          !  
     27   USE p4zprod         ! 
     28   USE p4zmort         ! 
     29   USE p4zmicro        !  
     30   USE p4zmeso         !  
     31   USE p4zrem          !  
    2432   USE p4zsed          !  
    2533   USE p4zlys          !  
    2634   USE p4zflx          !  
    2735 
    28    USE trdmld_trc_oce 
    29    USE trdmld_trc 
     36   USE prtctl_trc 
     37 
     38   USE trdmod_oce 
     39   USE trdmod_trc 
    3040 
    3141   USE sedmodel 
     
    3747 
    3848   !!---------------------------------------------------------------------- 
    39    !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
     49   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    4050   !! $Id$  
    41    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     51   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4252   !!---------------------------------------------------------------------- 
    4353 
     
    5969      INTEGER ::   jnt, jn 
    6070      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrpis   ! used for pisces sms trends 
     71      CHARACTER (len=25) :: charout 
    6172      !!--------------------------------------------------------------------- 
    6273 
    63       IF( kt == nittrc000  .AND. .NOT. ln_rsttr )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
     74      IF( kt == nit000 )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
    6475 
    65       IF( ndayflxtr /= nday ) THEN      ! New days 
     76      IF( ndayflxtr /= nday_year ) THEN      ! New days 
    6677         ! 
    67          ndayflxtr = nday 
     78         ndayflxtr = nday_year 
     79 
     80         IF(lwp) write(numout,*) 
     81         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year 
     82         IF(lwp) write(numout,*) '~~~~~~' 
    6883 
    6984         CALL p4z_che          ! computation of chemical constants 
     
    7186         ! 
    7287      ENDIF 
    73  
    7488 
    7589      DO jnt = 1, nrdttrc          ! Potential time splitting if requested 
     
    91105      END DO 
    92106 
     107 
    93108      IF( l_trdtrc ) THEN 
    94109          DO jn = jp_pcs0, jp_pcs1 
    95110            ztrpis(:,:,:) = tra(:,:,:,jn) 
    96             CALL trd_mod_trc( ztrpis, jn, jptrc_trd_sms, kt )   ! save trends 
     111            CALL trd_mod_trc( ztrpis, jn, jptra_trd_sms, kt )   ! save trends 
    97112          END DO 
    98113      END IF 
     
    121136      REAL(wp) ::  ztmas, ztmas1 
    122137 
    123       ! Initialization of chemical variables of the carbon cycle 
    124       ! -------------------------------------------------------- 
    125       DO jk = 1, jpk 
    126          DO jj = 1, jpj 
    127             DO ji = 1, jpi 
    128                ztmas   = tmask(ji,jj,jk) 
    129                ztmas1  = 1. - tmask(ji,jj,jk) 
    130                zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  ) 
    131                zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1 
    132                zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk ) 
    133                hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1 
     138      IF( .NOT. ln_rsttr ) THEN 
     139         ! Initialization of chemical variables of the carbon cycle 
     140         ! -------------------------------------------------------- 
     141         DO jk = 1, jpk 
     142            DO jj = 1, jpj 
     143               DO ji = 1, jpi 
     144                  ztmas   = tmask(ji,jj,jk) 
     145                  ztmas1  = 1. - tmask(ji,jj,jk) 
     146                  zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  ) 
     147                  zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1 
     148                  zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk ) 
     149                  hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1 
     150               END DO 
    134151            END DO 
    135152         END DO 
    136       END DO 
     153         ! 
     154      END IF 
     155 
     156      ! Time step duration for biology 
     157      xstep = rfact2 / rday 
     158 
     159      CALL p4z_sink_init      ! vertical flux of particulate organic matter 
     160      CALL p4z_opt_init       ! Optic: PAR in the water column 
     161      CALL p4z_lim_init       ! co-limitations by the various nutrients 
     162      CALL p4z_prod_init      ! phytoplankton growth rate over the global ocean.  
     163      CALL p4z_rem_init       ! remineralisation 
     164      CALL p4z_mort_init      ! phytoplankton mortality 
     165      CALL p4z_micro_init     ! microzooplankton 
     166      CALL p4z_meso_init      ! mesozooplankton 
     167      CALL p4z_sed_init       ! sedimentation 
     168      CALL p4z_lys_init       ! calcite saturation 
     169      CALL p4z_flx_init       ! gas exchange 
     170 
     171      ndayflxtr = 0 
    137172 
    138173   END SUBROUTINE trc_sms_pisces_init 
Note: See TracChangeset for help on using the changeset viewer.