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 7646 for trunk/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r6140 r7646  
    2020   USE oce_trc           ! shared variables between ocean and passive tracers 
    2121   USE trc               ! passive tracers common variables 
    22    USE trcnam_pisces     ! PISCES namelist 
    23    USE trcnam_cfc        ! CFC SMS namelist 
    24    USE trcnam_c14b       ! C14 SMS namelist 
    25    USE trcnam_my_trc     ! MY_TRC SMS namelist 
    2622   USE trd_oce        
    2723   USE trdtrc_oce 
     
    3430   PUBLIC trc_nam      ! called in trcini 
    3531 
     32   TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  ! type of tracer for saving if not key_iomput 
     33 
    3634   !!---------------------------------------------------------------------- 
    3735   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    5250      !!--------------------------------------------------------------------- 
    5351      INTEGER  ::   jn                  ! dummy loop indice 
    54       !                                   
    55       IF( .NOT.lk_offline )   CALL trc_nam_run     ! Parameters of the run  
     52      ! 
     53      IF( .NOT.l_offline )   CALL trc_nam_run     ! Parameters of the run                                   
    5654      !                
    57                               CALL trc_nam_trc     ! passive tracer informations 
     55      CALL trc_nam_trc     ! passive tracer informations 
    5856      !                                         
    59                               CALL trc_nam_dia     ! Parameters of additional diagnostics 
    60       !                                       
    61       ! 
    6257      IF( ln_rsttr                     )   ln_trcdta     = .FALSE.   ! restart : no need of clim data 
    6358      ! 
    6459      IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta     = .TRUE.   ! damping : need to have clim data 
    6560      ! 
    66       IF( .NOT.ln_trcdta               )   ln_trc_ini(:) = .FALSE. 
    67  
    68       IF(lwp) THEN                   ! control print 
    69          WRITE(numout,*) 
    70          WRITE(numout,*) ' Namelist : namtrc' 
    71          WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
    72          WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
    73          WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
    74          WRITE(numout,*) ' ' 
    75          DO jn = 1, jptra 
    76             WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn) 
    77          END DO 
    78          WRITE(numout,*) ' ' 
    79       ENDIF 
    8061 
    8162      IF(lwp) THEN                   ! control print 
     
    9677         ENDIF 
    9778      ENDIF 
    98  
    99        
    100       rdttrc = rdt * FLOAT( nn_dttrc )   ! passive tracer time-step 
    101    
    102       IF(lwp) THEN                   ! control print 
     79      ! 
     80      rdttrc = rdt * FLOAT( nn_dttrc )          ! passive tracer time-step 
     81      !  
     82      IF(lwp) THEN                              ! control print 
    10383        WRITE(numout,*)  
    10484        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc 
    10585        WRITE(numout,*)  
    10686      ENDIF 
    107  
    108  
    109 #if defined key_trdmxl_trc || defined key_trdtrc 
    110  
    111          REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends 
    112          READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905) 
    113 905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp ) 
    114  
    115          REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends 
    116          READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 ) 
    117 906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp ) 
    118          IF(lwm) WRITE ( numont, namtrc_trd ) 
    119  
    120          IF(lwp) THEN 
    121             WRITE(numout,*) 
    122             WRITE(numout,*) ' trd_mxl_trc_init : read namelist namtrc_trd                    ' 
    123             WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               ' 
    124             WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc 
    125             WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc 
    126             WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart 
    127             WRITE(numout,*) '   * flag to diagnose trends of                                 ' 
    128             WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant 
    129             WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc 
    130             DO jn = 1, jptra 
    131                IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn 
    132             END DO 
    133          ENDIF 
    134 #endif 
    135  
    136  
    137       ! Call the ice module for tracers 
    138       ! ------------------------------- 
    139                                   CALL trc_nam_ice 
    140  
    141       ! namelist of SMS 
    142       ! ---------------       
    143       IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model 
    144       ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used' 
    145       ENDIF 
    146  
    147       IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers 
    148       ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used' 
    149       ENDIF 
    150  
    151       IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers 
    152       ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used' 
    153       ENDIF 
    154  
    155       IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers 
    156       ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used' 
    157       ENDIF 
     87      ! 
     88      IF( l_trdtrc )        CALL trc_nam_trd    ! Passive tracer trends 
    15889      ! 
    15990   END SUBROUTINE trc_nam 
     
    16798      !! 
    16899      !!--------------------------------------------------------------------- 
    169       NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
     100      NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
    170101        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
    171102      ! 
     
    199130         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
    200131         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
    201          WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc  
    202132         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    203133         WRITE(numout,*) ' ' 
     
    206136    END SUBROUTINE trc_nam_run 
    207137 
    208  
    209    SUBROUTINE trc_nam_ice 
    210       !!--------------------------------------------------------------------- 
    211       !!                     ***  ROUTINE trc_nam_ice *** 
    212       !! 
    213       !! ** Purpose :   Read the namelist for the ice effect on tracers 
    214       !! 
    215       !! ** Method  : - 
    216       !! 
    217       !!--------------------------------------------------------------------- 
    218       INTEGER :: jn      ! dummy loop indices 
    219       INTEGER :: ios     ! Local integer output status for namelist read 
    220       ! 
    221       TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer 
    222       !! 
    223       NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer 
    224       !!--------------------------------------------------------------------- 
    225       ! 
    226       IF(lwp) THEN 
    227          WRITE(numout,*) 
    228          WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice' 
    229          WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    230       ENDIF 
    231  
    232       IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice') 
    233  
    234       ! 
    235       REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data 
    236       READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901) 
    237  901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp ) 
    238  
    239       REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients 
    240       READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 ) 
    241  902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp ) 
    242  
    243       IF( lwp ) THEN 
    244          WRITE(numout,*) ' ' 
    245          WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr 
    246          WRITE(numout,*) ' ' 
    247       ENDIF 
    248  
    249       ! Assign namelist stuff 
    250       DO jn = 1, jptra 
    251          trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio 
    252          trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr 
    253          cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o 
    254       END DO 
    255  
    256       IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice') 
    257       ! 
    258    END SUBROUTINE trc_nam_ice 
    259  
    260  
    261138   SUBROUTINE trc_nam_trc 
    262139      !!--------------------------------------------------------------------- 
     
    266143      !! 
    267144      !!--------------------------------------------------------------------- 
    268       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    269       INTEGER  ::   jn                  ! dummy loop indice 
    270       ! 
    271       TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
    272       !! 
    273       NAMELIST/namtrc/ sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo 
    274       !!--------------------------------------------------------------------- 
     145      INTEGER  ::   ios, ierr, icfc       ! Local integer output status for namelist read 
     146      !! 
     147      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, & 
     148         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d 
     149      !!--------------------------------------------------------------------- 
     150      ! Dummy settings to fill tracers data structure 
     151      !                  !   name   !   title   !   unit   !   init  !   sbc   !   cbc   !   obc  ! 
     152      sn_tracer = PTRACER( 'NONAME' , 'NOTITLE' , 'NOUNIT' , .false. , .false. , .false. , .false.) 
     153      ! 
    275154      IF(lwp) WRITE(numout,*) 
    276155      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists' 
     
    286165      IF(lwm) WRITE ( numont, namtrc ) 
    287166 
    288       DO jn = 1, jptra 
    289          ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
    290          ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
    291          ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
    292          ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
    293 #if defined key_my_trc 
    294          ln_trc_sbc(jn) =       sn_tracer(jn)%llsbc 
    295          ln_trc_cbc(jn) =       sn_tracer(jn)%llcbc 
    296          ln_trc_obc(jn) =       sn_tracer(jn)%llobc 
    297 #endif 
    298          ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
    299       END DO 
    300       ! 
     167      ! Control settings 
     168      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' ) 
     169      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jp_bgc = 0 
     170      ll_cfc = ln_cfc11 .OR. ln_cfc12 .OR. ln_sf6 
     171      ! 
     172      jptra       =  0 
     173      jp_pisces   =  0    ;   jp_pcs0  =  0    ;   jp_pcs1  = 0 
     174      jp_my_trc   =  0    ;   jp_myt0  =  0    ;   jp_myt1  = 0 
     175      jp_cfc      =  0    ;   jp_cfc0  =  0    ;   jp_cfc1  = 0 
     176      jp_age      =  0    ;   jp_c14   =  0 
     177      ! 
     178      IF( ln_pisces )  THEN 
     179         jp_pisces = jp_bgc 
     180         jp_pcs0   = 1 
     181         jp_pcs1   = jp_pisces 
     182      ENDIF 
     183      IF( ln_my_trc )  THEN 
     184          jp_my_trc = jp_bgc 
     185          jp_myt0   = 1 
     186          jp_myt1   = jp_my_trc 
     187      ENDIF 
     188      ! 
     189      jptra  = jp_bgc 
     190      ! 
     191      IF( ln_age )    THEN 
     192         jptra     = jptra + 1 
     193         jp_age    = jptra 
     194      ENDIF 
     195      IF( ln_cfc11 )  jp_cfc = jp_cfc + 1 
     196      IF( ln_cfc12 )  jp_cfc = jp_cfc + 1 
     197      IF( ln_sf6   )  jp_cfc = jp_cfc + 1 
     198      IF( ll_cfc )    THEN 
     199          jptra     = jptra + jp_cfc 
     200          jp_cfc0   = jptra - jp_cfc + 1 
     201          jp_cfc1   = jptra 
     202      ENDIF 
     203      IF( ln_c14 )    THEN 
     204           jptra     = jptra + 1 
     205           jp_c14    = jptra 
     206      ENDIF 
     207      ! 
     208      IF( jptra == 0 )   CALL ctl_stop( 'All TOP tracers disabled: change namtrc setting or check if key_top is active' ) 
     209      ! 
     210      IF(lwp) THEN                   ! control print 
     211         WRITE(numout,*) 
     212         WRITE(numout,*) ' Namelist : namtrc' 
     213         WRITE(numout,*) '   Total number of passive tracers              jptra         = ', jptra 
     214         WRITE(numout,*) '   Total number of BGC tracers                  jp_bgc        = ', jp_bgc 
     215         WRITE(numout,*) '   Simulating PISCES model                      ln_pisces     = ', ln_pisces 
     216         WRITE(numout,*) '   Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc 
     217         WRITE(numout,*) '   Simulating water mass age                    ln_age        = ', ln_age 
     218         WRITE(numout,*) '   Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11 
     219         WRITE(numout,*) '   Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12 
     220         WRITE(numout,*) '   Simulating SF6 passive tracer                ln_sf6        = ', ln_sf6 
     221         WRITE(numout,*) '   Total number of CFCs tracers                 jp_cfc        = ', jp_cfc 
     222         WRITE(numout,*) '   Simulating C14   passive tracer              ln_c14        = ', ln_c14 
     223         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
     224         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
     225         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
     226         WRITE(numout,*) ' ' 
     227         WRITE(numout,*) ' ' 
     228      ENDIF 
     229      ! 
     230      IF( ll_cfc .OR. ln_c14 ) THEN 
     231        !                             ! Open namelist files 
     232        CALL ctl_opn( numtrc_ref, 'namelist_trc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     233        CALL ctl_opn( numtrc_cfg, 'namelist_trc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     234        IF(lwm) CALL ctl_opn( numonr, 'output.namelist.trc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     235        ! 
     236      ENDIF 
     237 
    301238   END SUBROUTINE trc_nam_trc 
    302239 
    303  
    304    SUBROUTINE trc_nam_dia 
     240   SUBROUTINE trc_nam_trd 
    305241      !!--------------------------------------------------------------------- 
    306242      !!                     ***  ROUTINE trc_nam_dia  *** 
     
    312248      !!                ( (PISCES, CFC, MY_TRC ) 
    313249      !!--------------------------------------------------------------------- 
     250 
     251#if defined key_trdmxl_trc  || defined key_trdtrc 
    314252      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    315253      INTEGER ::  ierr 
    316254      !! 
    317 #if defined key_trdmxl_trc  || defined key_trdtrc 
    318255      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
    319256         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, & 
    320257         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
    321 #endif 
    322       NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio 
    323258      !!--------------------------------------------------------------------- 
    324259 
    325260      IF(lwp) WRITE(numout,*) 
    326       IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
     261      IF(lwp) WRITE(numout,*) 'trc_nam_trd : read the passive tracer diagnostics options' 
    327262      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    328263 
    329       REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics 
    330       READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903) 
    331 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp ) 
    332  
    333       REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics 
    334       READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 ) 
    335 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp ) 
    336       IF(lwm) WRITE ( numont, namtrc_dia ) 
     264      ! 
     265      ALLOCATE( ln_trdtrc(jptra) )  
     266      ! 
     267      REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends 
     268      READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905) 
     269905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp ) 
     270 
     271      REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends 
     272      READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 ) 
     273906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp ) 
     274      IF(lwm) WRITE ( numont, namtrc_trd ) 
    337275 
    338276      IF(lwp) THEN 
    339277         WRITE(numout,*) 
    340          WRITE(numout,*) 
    341          WRITE(numout,*) ' Namelist : namtrc_dia' 
    342          WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc 
    343          WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio 
    344          WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia 
    345          WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
    346          WRITE(numout,*) ' ' 
    347       ENDIF 
    348  
    349       IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN  
    350          ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
    351            &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
    352            &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr )  
    353          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' ) 
    354          ! 
    355          trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' '  
    356          trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' '  
    357          ! 
    358       ENDIF 
    359  
    360       IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN 
    361          ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , & 
    362            &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr )  
    363          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' ) 
    364          ! 
    365          trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' '  
    366          ! 
    367       ENDIF 
    368       ! 
    369    END SUBROUTINE trc_nam_dia 
     278         WRITE(numout,*) ' trd_mxl_trc_init : read namelist namtrc_trd                    ' 
     279         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               ' 
     280         WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc 
     281         WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc 
     282         WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart 
     283         WRITE(numout,*) '   * flag to diagnose trends of                                 ' 
     284         WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant 
     285         WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc 
     286         DO jn = 1, jptra 
     287            IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn 
     288         END DO 
     289      ENDIF 
     290#endif 
     291      ! 
     292   END SUBROUTINE trc_nam_trd 
    370293 
    371294#else 
Note: See TracChangeset for help on using the changeset viewer.