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 7068 for branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdmxl_trc.F90 – NEMO

Ignore:
Timestamp:
2016-10-21T17:38:13+02:00 (8 years ago)
Author:
cetlod
Message:

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdmxl_trc.F90

    r6140 r7068  
    4141   PUBLIC trd_mxl_trc 
    4242   PUBLIC trd_mxl_trc_alloc 
    43    PUBLIC trd_mxl_bio 
    4443   PUBLIC trd_mxl_trc_init 
    4544   PUBLIC trd_mxl_trc_zint 
    46    PUBLIC trd_mxl_bio_zint 
    4745 
    4846   CHARACTER (LEN=40) ::  clhstnam                                ! name of the trends NetCDF file 
    4947   INTEGER ::   nmoymltrd 
    50    INTEGER, ALLOCATABLE, SAVE, DIMENSION(:) ::   ndextrd1 
    51    INTEGER, DIMENSION(jptra) ::   nidtrd, nh_t 
     48   INTEGER, ALLOCATABLE, SAVE, DIMENSION(:) ::   ndextrd1, nidtrd, nh_t 
    5249   INTEGER ::   ndimtrd1                         
    5350   INTEGER, SAVE ::  ionce, icount 
    54 #if defined key_pisces_reduced 
    55    INTEGER ::   nidtrdbio, nh_tb 
    56    INTEGER, SAVE ::  ioncebio, icountbio 
    57    INTEGER, SAVE ::   nmoymltrdbio 
    58 #endif 
    5951   LOGICAL :: llwarn  = .TRUE.                                    ! this should always be .TRUE. 
    6052   LOGICAL :: lldebug = .TRUE. 
    6153 
    6254   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  ztmltrd2   ! 
    63 #if defined key_pisces_reduced 
    64    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ztmltrdbio2  ! only needed for mean diagnostics in trd_mxl_bio() 
    65 #endif 
    6655 
    6756   !! * Substitutions 
     
    7968      !!---------------------------------------------------------------------- 
    8069      ALLOCATE( ztmltrd2(jpi,jpj,jpltrd_trc,jptra) ,      & 
    81 #if defined key_pisces_reduced 
    82          &      ztmltrdbio2(jpi,jpj,jpdiabio)      ,      & 
    83 #endif 
    84          &      ndextrd1(jpi*jpj)                  ,  STAT=trd_mxl_trc_alloc) 
     70         &      ndextrd1(jpi*jpj), nidtrd(jptra), nh_t(jptra),  STAT=trd_mxl_trc_alloc) 
    8571         ! 
    8672      IF( lk_mpp                )   CALL mpp_sum ( trd_mxl_trc_alloc ) 
     
    131117         SELECT CASE ( nn_ctls_trc )                                ! choice of the control surface 
    132118            CASE ( -2  )   ;   STOP 'trdmxl_trc : not ready '     !     -> isopycnal surface (see ???) 
    133 #if defined key_pisces || defined key_pisces_reduced 
    134119            CASE ( -1  )   ;   nmld_trc(:,:) = neln(:,:)          !     -> euphotic layer with light criterion 
    135 #endif 
    136120            CASE (  0  )   ;   nmld_trc(:,:) = nmln(:,:)          !     -> ML with density criterion (see zdfmxl) 
    137121            CASE (  1  )   ;   nmld_trc(:,:) = nbol_trc(:,:)          !     -> read index from file 
     
    207191      ! 
    208192   END SUBROUTINE trd_mxl_trc_zint 
    209  
    210  
    211    SUBROUTINE trd_mxl_bio_zint( ptrc_trdmxl, ktrd ) 
    212       !!---------------------------------------------------------------------- 
    213       !!                  ***  ROUTINE trd_mxl_bio_zint  *** 
    214       !! 
    215       !! ** Purpose :   Compute the vertical average of the 3D fields given as arguments 
    216       !!                to the subroutine. This vertical average is performed from ocean 
    217       !!                surface down to a chosen control surface. 
    218       !! 
    219       !! ** Method/usage : 
    220       !!      The control surface can be either a mixed layer depth (time varying) 
    221       !!      or a fixed surface (jk level or bowl). 
    222       !!      Choose control surface with nctls in namelist NAMTRD : 
    223       !!        nctls_trc = 0  : use mixed layer with density criterion 
    224       !!        nctls_trc = 1  : read index from file 'ctlsurf_idx' 
    225       !!        nctls_trc > 1  : use fixed level surface jk = nctls_trc 
    226       !!      Note: in the remainder of the routine, the volume between the 
    227       !!            surface and the control surface is called "mixed-layer" 
    228       !!---------------------------------------------------------------------- 
    229       !! 
    230       INTEGER                         , INTENT(in) ::   ktrd          ! bio trend index 
    231       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) ::   ptrc_trdmxl   ! passive trc trend 
    232 #if defined key_pisces_reduced 
    233       ! 
    234       INTEGER ::   ji, jj, jk, isum 
    235       REAL(wp), POINTER, DIMENSION(:,:) :: zvlmsk 
    236       !!---------------------------------------------------------------------- 
    237  
    238       CALL wrk_alloc( jpi, jpj, zvlmsk ) 
    239  
    240       ! I. Definition of control surface and integration weights 
    241       ! -------------------------------------------------------- 
    242       !            ==> only once per time step <== 
    243  
    244       IF( icountbio == 1 ) THEN 
    245          ! 
    246          tmltrd_bio(:,:,:) = 0.e0    ! <<< reset trend arrays to zero 
    247          ! ... Set nmld(ji,jj) = index of first T point below control surf. or outside mixed-layer 
    248          SELECT CASE ( nn_ctls_trc )                                    ! choice of the control surface 
    249             CASE ( -2  )   ;   STOP 'trdmxl_trc : not ready '     !     -> isopycnal surface (see ???) 
    250             CASE ( -1  )   ;   nmld_trc(:,:) = neln(:,:)          !     -> euphotic layer with light criterion 
    251             CASE (  0  )   ;   nmld_trc(:,:) = nmln(:,:)          !     -> ML with density criterion (see zdfmxl) 
    252             CASE (  1  )   ;   nmld_trc(:,:) = nbol_trc(:,:)          !     -> read index from file 
    253             CASE (  2: )   ;   nn_ctls_trc = MIN( nn_ctls_trc, jpktrd_trc - 1 ) 
    254                                nmld_trc(:,:) = nn_ctls_trc + 1          !     -> model level 
    255          END SELECT 
    256  
    257          ! ... Compute ndextrd1 and ndimtrd1 only once 
    258          IF( ioncebio == 1 ) THEN 
    259             ! 
    260             ! Check of validity : nmld_trc(ji,jj) <= jpktrd_trc 
    261             isum        = 0 
    262             zvlmsk(:,:) = 0.e0 
    263  
    264             IF( jpktrd_trc < jpk ) THEN 
    265                DO jj = 1, jpj 
    266                   DO ji = 1, jpi 
    267                      IF( nmld_trc(ji,jj) <= jpktrd_trc ) THEN 
    268                         zvlmsk(ji,jj) = tmask(ji,jj,1) 
    269                      ELSE 
    270                         isum = isum + 1 
    271                         zvlmsk(ji,jj) = 0. 
    272                      END IF 
    273                   END DO 
    274                END DO 
    275             END IF 
    276  
    277             ! Index of ocean points (2D only) 
    278             IF( isum > 0 ) THEN 
    279                WRITE(numout,*)' tmltrd_trc : Number of invalid points nmld_trc > jpktrd', isum 
    280                CALL wheneq( jpi*jpj, zvlmsk(:,:) , 1, 1., ndextrd1, ndimtrd1 ) 
    281             ELSE 
    282                CALL wheneq( jpi*jpj, tmask(:,:,1), 1, 1., ndextrd1, ndimtrd1 ) 
    283             END IF 
    284  
    285             ioncebio = 0                  ! no more pass here 
    286             ! 
    287          END IF !  ( ioncebio == 1 ) 
    288  
    289          ! ... Weights for vertical averaging 
    290          wkx_trc(:,:,:) = 0.e0 
    291          DO jk = 1, jpktrd_trc         ! initialize wkx_trc with vertical scale factor in mixed-layer 
    292             DO jj = 1,jpj 
    293               DO ji = 1,jpi 
    294                   IF( jk - nmld_trc(ji,jj) < 0. )   wkx_trc(ji,jj,jk) = e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
    295                END DO 
    296             END DO 
    297          END DO 
    298  
    299          rmld_trc(:,:) = 0. 
    300          DO jk = 1, jpktrd_trc         ! compute mixed-layer depth : rmld_trc 
    301             rmld_trc(:,:) = rmld_trc(:,:) + wkx_trc(:,:,jk) 
    302          END DO 
    303  
    304          DO jk = 1, jpktrd_trc         ! compute integration weights 
    305             wkx_trc(:,:,jk) = wkx_trc(:,:,jk) / MAX( 1., rmld_trc(:,:) ) 
    306          END DO 
    307  
    308          icountbio = 0                    ! <<< flag = off : control surface & integr. weights 
    309          !                             !     computed only once per time step 
    310       END IF ! ( icountbio == 1 ) 
    311  
    312       ! II. Vertical integration of trends in the mixed-layer 
    313       ! ----------------------------------------------------- 
    314  
    315  
    316       DO jk = 1, jpktrd_trc 
    317          tmltrd_bio(:,:,ktrd) = tmltrd_bio(:,:,ktrd) + ptrc_trdmxl(:,:,jk) * wkx_trc(:,:,jk) 
    318       END DO 
    319  
    320       CALL wrk_dealloc( jpi, jpj, zvlmsk ) 
    321 #endif 
    322       ! 
    323    END SUBROUTINE trd_mxl_bio_zint 
    324193 
    325194 
     
    877746 
    878747 
    879    SUBROUTINE trd_mxl_bio( kt ) 
    880       !!---------------------------------------------------------------------- 
    881       !!                  ***  ROUTINE trd_mld  *** 
    882       !! 
    883       !! ** Purpose :  Compute and cumulate the mixed layer biological trends over an analysis 
    884       !!               period, and write NetCDF outputs. 
    885       !! 
    886       !! ** Method/usage : 
    887       !!          The stored trends can be chosen twofold (according to the ln_trdmxl_trc_instant 
    888       !!          logical namelist variable) : 
    889       !!          1) to explain the difference between initial and final 
    890       !!             mixed-layer T & S (where initial and final relate to the 
    891       !!             current analysis window, defined by ntrd in the namelist) 
    892       !!          2) to explain the difference between the current and previous 
    893       !!             TIME-AVERAGED mixed-layer T & S (where time-averaging is 
    894       !!             performed over each analysis window). 
    895       !! 
    896       !! ** Consistency check : 
    897       !!        If the control surface is fixed ( nctls > 1 ), the residual term (dh/dt 
    898       !!        entrainment) should be zero, at machine accuracy. Note that in the case 
    899       !!        of time-averaged mixed-layer fields, this residual WILL NOT BE ZERO 
    900       !!        over the first two analysis windows (except if restart). 
    901       !!        N.B. For ORCA2_LIM, use e.g. ntrd=5, ucf=1., nctls=8 
    902       !!             for checking residuals. 
    903       !!             On a NEC-SX5 computer, this typically leads to: 
    904       !!                   O(1.e-20) temp. residuals (tml_res) when ln_trdmxl_trc_instant=.false. 
    905       !!                   O(1.e-21) temp. residuals (tml_res) when ln_trdmxl_trc_instant=.true. 
    906       !! 
    907       !! ** Action : 
    908       !!       At each time step, mixed-layer averaged trends are stored in the 
    909       !!       tmltrd(:,:,jpmxl_xxx) array (see trdmxl_oce.F90 for definitions of jpmxl_xxx). 
    910       !!       This array is known when trd_mld is called, at the end of the stp subroutine, 
    911       !!       except for the purely vertical K_z diffusion term, which is embedded in the 
    912       !!       lateral diffusion trend. 
    913       !! 
    914       !!       In I), this K_z term is diagnosed and stored, thus its contribution is removed 
    915       !!       from the lateral diffusion trend. 
    916       !!       In II), the instantaneous mixed-layer T & S are computed, and misc. cumulative 
    917       !!       arrays are updated. 
    918       !!       In III), called only once per analysis window, we compute the total trends, 
    919       !!       along with the residuals and the Asselin correction terms. 
    920       !!       In IV), the appropriate trends are written in the trends NetCDF file. 
    921       !! 
    922       !! References : 
    923       !!       - Vialard & al. 
    924       !!       - See NEMO documentation (in preparation) 
    925       !!---------------------------------------------------------------------- 
    926       INTEGER, INTENT( in ) ::   kt                       ! ocean time-step index 
    927 #if defined key_pisces_reduced 
    928       INTEGER  ::  jl, it, itmod 
    929       LOGICAL  :: llwarn  = .TRUE., lldebug = .TRUE. 
    930       REAL(wp) :: zfn, zfn2 
    931       !!---------------------------------------------------------------------- 
    932       ! ... Warnings 
    933       IF( nn_dttrc  /= 1  ) CALL ctl_stop( " Be careful, trends diags never validated " ) 
    934  
    935       ! ====================================================================== 
    936       ! II. Cumulate the trends over the analysis window 
    937       ! ====================================================================== 
    938  
    939       ztmltrdbio2(:,:,:) = 0.e0  ! <<< reset arrays to zero 
    940  
    941       ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window 
    942       ! ------------------------------------------------------------------------ 
    943       IF( kt == nittrc000 + nn_dttrc ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1) 
    944          ! 
    945          tmltrd_csum_ub_bio (:,:,:) = 0.e0 
    946          ! 
    947       END IF 
    948  
    949       ! II.4 Cumulated trends over the analysis period 
    950       ! ---------------------------------------------- 
    951       ! 
    952       !         [  1rst analysis window ] [     2nd analysis window     ] 
    953       ! 
    954       ! 
    955       !     o---[--o-----o-----o-----o--]-[--o-----o-----o-----o-----o--]---o-----o--> time steps 
    956       !                            ntrd                             2*ntrd       etc. 
    957       !     1      2     3     4    =5 e.g.                          =10 
    958       ! 
    959       IF( ( kt >= 2 ).OR.( ln_rsttr ) ) THEN 
    960          ! 
    961          nmoymltrdbio = nmoymltrdbio + 1 
    962  
    963          ! ... Trends associated with the time mean of the ML passive tracers 
    964          tmltrd_sum_bio    (:,:,:) = tmltrd_sum_bio    (:,:,:) + tmltrd_bio    (:,:,:) 
    965          tmltrd_csum_ln_bio(:,:,:) = tmltrd_csum_ln_bio(:,:,:) + tmltrd_sum_bio(:,:,:) 
    966          ! 
    967       END IF 
    968  
    969       ! ====================================================================== 
    970       ! III. Prepare fields for output (get here ONCE PER ANALYSIS PERIOD) 
    971       ! ====================================================================== 
    972  
    973       ! Convert to appropriate physical units 
    974       tmltrd_bio(:,:,:) = tmltrd_bio(:,:,:) * rn_ucf_trc 
    975  
    976       MODULO_NTRD : IF( MOD( kt, nn_trd_trc ) == 0 ) THEN      ! nitend MUST be multiple of ntrd 
    977          ! 
    978          zfn  = float(nmoymltrdbio)    ;    zfn2 = zfn * zfn 
    979  
    980          ! III.1 Prepare fields for output ("instantaneous" diagnostics) 
    981          ! ------------------------------------------------------------- 
    982  
    983 #if defined key_diainstant 
    984          STOP 'tmltrd_bio : key_diainstant was never checked within trdmxl. Comment this to proceed.' 
    985 #endif 
    986          ! III.2 Prepare fields for output ("mean" diagnostics) 
    987          ! ---------------------------------------------------- 
    988  
    989          ztmltrdbio2(:,:,:) = tmltrd_csum_ub_bio(:,:,:) + tmltrd_csum_ln_bio(:,:,:) 
    990  
    991          !-- Lateral boundary conditions 
    992          IF ( cp_cfg .NE. 'gyre' ) THEN            ! other than GYRE configuration  
    993             ! ES_B27_CD_WARN : lbc inutile GYRE, cf. + haut 
    994             DO jn = 1, jpdiabio 
    995               CALL lbc_lnk( ztmltrdbio2(:,:,jn), 'T', 1. ) 
    996             ENDDO 
    997          ENDIF 
    998  
    999          IF( lldebug ) THEN 
    1000             ! 
    1001             WRITE(numout,*) 'trd_mxl_bio : write trends in the Mixed Layer for debugging process:' 
    1002             WRITE(numout,*) '~~~~~~~~~~~  ' 
    1003             WRITE(numout,*) 'TRC kt = ', kt, 'nmoymltrdbio = ', nmoymltrdbio 
    1004             WRITE(numout,*) 
    1005  
    1006             DO jl = 1, jpdiabio 
    1007               IF( ln_trdmxl_trc_instant ) THEN 
    1008                   WRITE(numout,97) 'TRC jl =', jl, ' bio TREND INDEX  = ', jl, & 
    1009                      & ' SUM tmltrd_bio : ', SUM2D(tmltrd_bio(:,:,jl)) 
    1010               ELSE 
    1011                   WRITE(numout,97) 'TRC jl =', jl, ' bio TREND INDEX  = ', jl, & 
    1012                      & ' SUM ztmltrdbio2 : ', SUM2D(ztmltrdbio2(:,:,jl)) 
    1013               endif 
    1014             END DO 
    1015  
    1016 97          FORMAT(a10, i3, 2x, a30, i3, a20, 2x, g20.10) 
    1017 98          FORMAT(a10, i3, 2x, a30, 2x, g20.10) 
    1018 99          FORMAT('TRC jj =', i3,' : ', 10(g10.3,2x)) 
    1019             WRITE(numout,*) 
    1020             ! 
    1021          ENDIF 
    1022  
    1023          ! III.3 Time evolution array swap 
    1024          ! ------------------------------- 
    1025  
    1026          ! For passive tracer mean diagnostics 
    1027          tmltrd_csum_ub_bio (:,:,:) = zfn * tmltrd_sum_bio(:,:,:) - tmltrd_csum_ln_bio(:,:,:) 
    1028  
    1029          ! III.4 Convert to appropriate physical units 
    1030          ! ------------------------------------------- 
    1031          ztmltrdbio2    (:,:,:) = ztmltrdbio2    (:,:,:) * rn_ucf_trc/zfn2 
    1032  
    1033       END IF MODULO_NTRD 
    1034  
    1035       ! ====================================================================== 
    1036       ! IV. Write trends in the NetCDF file 
    1037       ! ====================================================================== 
    1038  
    1039       ! IV.1 Code for IOIPSL/NetCDF output 
    1040       ! ---------------------------------- 
    1041  
    1042       ! define time axis 
    1043       itmod = kt - nittrc000 + 1 
    1044       it    = kt 
    1045  
    1046       IF( lwp .AND. MOD( itmod , nn_trd_trc ) == 0 ) THEN 
    1047          WRITE(numout,*) ' ' 
    1048          WRITE(numout,*) 'trd_mxl_bio : write ML bio trends in the NetCDF file :' 
    1049          WRITE(numout,*) '~~~~~~~~~~~ ' 
    1050          WRITE(numout,*) '          ', TRIM(clhstnam), ' at kt = ', kt 
    1051          WRITE(numout,*) '          N.B. nmoymltrdbio = ', nmoymltrdbio 
    1052          WRITE(numout,*) ' ' 
    1053       END IF 
    1054  
    1055  
    1056       ! 2. Start writing data 
    1057       ! --------------------- 
    1058  
    1059       NETCDF_OUTPUT : IF( ln_trdmxl_trc_instant ) THEN    ! <<< write the trends for passive tracer instant. diags 
    1060          ! 
    1061             DO jl = 1, jpdiabio 
    1062                CALL histwrite( nidtrdbio,TRIM("ML_"//ctrd_bio(jl,2)) ,            & 
    1063                     &          it, tmltrd_bio(:,:,jl), ndimtrd1, ndextrd1 ) 
    1064             END DO 
    1065  
    1066  
    1067          IF( kt == nitend )   CALL histclo( nidtrdbio ) 
    1068  
    1069       ELSE    ! <<< write the trends for passive tracer mean diagnostics 
    1070  
    1071             DO jl = 1, jpdiabio 
    1072                CALL histwrite( nidtrdbio, TRIM("ML_"//ctrd_bio(jl,2)) ,            & 
    1073                     &          it, ztmltrdbio2(:,:,jl), ndimtrd1, ndextrd1 ) 
    1074             END DO 
    1075  
    1076             IF( kt == nitend )   CALL histclo( nidtrdbio ) 
    1077             ! 
    1078       END IF NETCDF_OUTPUT 
    1079  
    1080       ! Compute the control surface (for next time step) : flag = on 
    1081       icountbio = 1 
    1082  
    1083  
    1084  
    1085       IF( MOD( itmod, nn_trd_trc ) == 0 ) THEN 
    1086          ! 
    1087          ! III.5 Reset cumulative arrays to zero 
    1088          ! ------------------------------------- 
    1089          nmoymltrdbio = 0 
    1090          tmltrd_csum_ln_bio (:,:,:) = 0.e0 
    1091          tmltrd_sum_bio     (:,:,:) = 0.e0 
    1092       END IF 
    1093  
    1094       ! ====================================================================== 
    1095       ! Write restart file 
    1096       ! ====================================================================== 
    1097  
    1098 ! restart write is done in trd_mxl_trc_write which is called by trd_mxl_bio (Marina) 
    1099 ! 
    1100 #endif 
    1101    END SUBROUTINE trd_mxl_bio 
    1102  
    1103  
    1104748   REAL FUNCTION sum2d( ztab ) 
    1105749      !!---------------------------------------------------------------------- 
     
    1191835      tmltrd_csum_ln_trc (:,:,:,:) = 0.e0   ;   rmld_sum_trc       (:,:)     = 0.e0 
    1192836 
    1193 #if defined key_pisces_reduced 
    1194       nmoymltrdbio   = 0 
    1195       tmltrd_sum_bio     (:,:,:) = 0.e0     ;   tmltrd_csum_ln_bio (:,:,:) = 0.e0 
    1196       DO jl = 1, jp_pisces_trd 
    1197           ctrd_bio(jl,1) = ctrbil(jl)   ! long name 
    1198           ctrd_bio(jl,2) = ctrbio(jl)   ! short name 
    1199        ENDDO 
    1200 #endif 
    1201  
    1202837      IF( ln_rsttr .AND. ln_trdmxl_trc_restart ) THEN 
    1203838         CALL trd_mxl_trc_rst_read 
     
    1208843         tml_sumb_trc       (:,:,:)   = 0.e0   ;   tmltrd_csum_ub_trc (:,:,:,:) = 0.e0     ! mean 
    1209844         tmltrd_atf_sumb_trc(:,:,:)   = 0.e0   ;   tmltrd_rad_sumb_trc(:,:,:)   = 0.e0  
    1210 #if defined key_pisces_reduced 
    1211          tmltrd_csum_ub_bio (:,:,:) = 0.e0 
    1212 #endif 
    1213845 
    1214846       ENDIF 
     
    1216848      icount = 1   ;   ionce  = 1  ! open specifier    
    1217849 
    1218 #if defined key_pisces_reduced 
    1219       icountbio = 1   ;   ioncebio  = 1  ! open specifier 
    1220 #endif 
    1221850 
    1222851      ! I.3 Read control surface from file ctlsurf_idx 
     
    1308937      END DO 
    1309938 
    1310 #if defined key_pisces_reduced 
    1311           !-- Create a NetCDF file and enter the define mode 
    1312           CALL dia_nam( clhstnam, nn_trd_trc, 'trdbio' ) 
    1313           CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    1314              &             1, jpi, 1, jpj, iiter, zjulian, rdt, nh_tb, nidtrdbio, domain_id=nidom, snc4chunks=snc4set ) 
    1315 #endif 
    1316  
    1317939      !-- Define physical units 
    1318940      IF( rn_ucf_trc == 1. ) THEN 
     
    1354976      END DO 
    1355977 
    1356 #if defined key_pisces_reduced 
    1357       DO jl = 1, jp_pisces_trd 
    1358          CALL histdef(nidtrdbio, TRIM("ML_"//ctrd_bio(jl,2)), TRIM(clmxl//" ML_"//ctrd_bio(jl,1))   ,            & 
    1359              &    cltrcu, jpi, jpj, nh_tb, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) ! IOIPSL: time mean 
    1360       END DO                                                                         ! if zsto=rdt above 
    1361 #endif 
    1362  
    1363978      !-- Leave IOIPSL/NetCDF define mode 
    1364979      DO jn = 1, jptra 
     
    1366981      END DO 
    1367982 
    1368 #if defined key_pisces_reduced 
    1369       !-- Leave IOIPSL/NetCDF define mode 
    1370       CALL histend( nidtrdbio, snc4set ) 
    1371  
    1372983      IF(lwp) WRITE(numout,*) 
    1373        IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization for ML bio trends' 
    1374 #endif 
    1375984 
    1376985   END SUBROUTINE trd_mxl_trc_init 
     
    1385994      WRITE(*,*) 'trd_mxl_trc: You should not have seen this print! error?', kt 
    1386995   END SUBROUTINE trd_mxl_trc 
    1387    SUBROUTINE trd_mxl_bio( kt ) 
    1388       INTEGER, INTENT( in) ::   kt 
    1389       WRITE(*,*) 'trd_mxl_bio: You should not have seen this print! error?', kt 
    1390    END SUBROUTINE trd_mxl_bio 
    1391996   SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn ) 
    1392997      INTEGER               , INTENT( in ) ::  ktrd, kjn              ! ocean trend index and passive tracer rank 
Note: See TracChangeset for help on using the changeset viewer.