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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r7646 r9169  
    1818   !!   trc_nam    :  Read and print options for the passive tracer run (namelist) 
    1919   !!---------------------------------------------------------------------- 
    20    USE oce_trc           ! shared variables between ocean and passive tracers 
    21    USE trc               ! passive tracers common variables 
    22    USE trd_oce        
    23    USE trdtrc_oce 
    24    USE iom               ! I/O manager 
     20   USE oce_trc     ! shared variables between ocean and passive tracers 
     21   USE trc         ! passive tracers common variables 
     22   USE trd_oce     !        
     23   USE trdtrc_oce  ! 
     24   USE iom         ! I/O manager 
    2525 
    2626   IMPLICIT NONE 
    2727   PRIVATE  
    2828 
    29    PUBLIC trc_nam_run  ! called in trcini 
    30    PUBLIC trc_nam      ! called in trcini 
    31  
    32    TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  ! type of tracer for saving if not key_iomput 
     29   PUBLIC   trc_nam_run  ! called in trcini 
     30   PUBLIC   trc_nam      ! called in trcini 
     31 
     32   TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  !: type of tracer for saving if not key_iomput 
    3333 
    3434   !!---------------------------------------------------------------------- 
     
    4949      !!                ( (PISCES, CFC, MY_TRC ) 
    5050      !!--------------------------------------------------------------------- 
    51       INTEGER  ::   jn                  ! dummy loop indice 
     51      INTEGER  ::   jn   ! dummy loop indice 
     52      !!--------------------------------------------------------------------- 
    5253      ! 
    5354      IF( .NOT.l_offline )   CALL trc_nam_run     ! Parameters of the run                                   
    5455      !                
    55       CALL trc_nam_trc     ! passive tracer informations 
     56      CALL trc_nam_trc                            ! passive tracer informations 
    5657      !                                         
    57       IF( ln_rsttr                     )   ln_trcdta     = .FALSE.   ! restart : no need of clim data 
    58       ! 
    59       IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta     = .TRUE.   ! damping : need to have clim data 
    60       ! 
    61  
     58      IF( ln_rsttr                     )   ln_trcdta = .FALSE.   ! restart : no need of clim data 
     59      ! 
     60      IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta = .TRUE.    ! damping : need to have clim data 
     61      ! 
     62      ! 
    6263      IF(lwp) THEN                   ! control print 
    6364         IF( ln_rsttr ) THEN 
    6465            WRITE(numout,*) 
    65             WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
    66             WRITE(numout,*) 
     66            WRITE(numout,*) '   ==>>>   Read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
    6767         ENDIF 
    6868         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN 
    6969            WRITE(numout,*) 
    70             WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies ' 
    71             WRITE(numout,*) 
     70            WRITE(numout,*) '   ==>>>   Some of the passive tracers are initialised from climatologies ' 
    7271         ENDIF 
    7372         IF( .NOT.ln_trcdta ) THEN 
    7473            WRITE(numout,*) 
    75             WRITE(numout,*) '  All the passive tracers are initialised with constant values ' 
    76             WRITE(numout,*) 
     74            WRITE(numout,*) '   ==>>>   All the passive tracers are initialised with constant values ' 
    7775         ENDIF 
    7876      ENDIF 
     
    8280      IF(lwp) THEN                              ! control print 
    8381        WRITE(numout,*)  
    84         WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc 
    85         WRITE(numout,*)  
     82        WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = nn_dttrc*rdt = ', rdttrc 
    8683      ENDIF 
    8784      ! 
     
    9895      !! 
    9996      !!--------------------------------------------------------------------- 
     97      INTEGER  ::   ios   ! Local integer 
     98      !! 
    10099      NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
    101100        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
    102       ! 
    103       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    104       !!--------------------------------------------------------------------- 
    105       ! 
     101      !!--------------------------------------------------------------------- 
     102      ! 
     103      IF(lwp) WRITE(numout,*) 
    106104      IF(lwp) WRITE(numout,*) 'trc_nam_run : read the passive tracer namelists' 
    107       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    108  
     105      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
     106      ! 
    109107      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    110108      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    111109      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 ) 
    112  
     110      ! 
    113111      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    114112      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901) 
    115 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    116  
     113901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    117114      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
    118115      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 ) 
    119 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
    120       IF(lwm) WRITE ( numont, namtrc_run ) 
    121  
    122       !  computes the first time step of tracer model 
    123       nittrc000 = nit000 + nn_dttrc - 1 
     116902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     117      IF(lwm) WRITE( numont, namtrc_run ) 
     118 
     119      nittrc000 = nit000 + nn_dttrc - 1      ! first time step of tracer model 
    124120 
    125121      IF(lwp) THEN                   ! control print 
    126          WRITE(numout,*) 
    127          WRITE(numout,*) ' Namelist : namtrc_run' 
    128          WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
    129          WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
    130          WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
    131          WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
    132          WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    133          WRITE(numout,*) ' ' 
     122         WRITE(numout,*) '   Namelist : namtrc_run' 
     123         WRITE(numout,*) '      time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
     124         WRITE(numout,*) '      restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
     125         WRITE(numout,*) '      control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
     126         WRITE(numout,*) '      first time step for pass. trac.              nittrc000     = ', nittrc000 
     127         WRITE(numout,*) '      Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    134128      ENDIF 
    135129      ! 
    136130    END SUBROUTINE trc_nam_run 
    137131 
     132 
    138133   SUBROUTINE trc_nam_trc 
    139134      !!--------------------------------------------------------------------- 
     
    143138      !! 
    144139      !!--------------------------------------------------------------------- 
    145       INTEGER  ::   ios, ierr, icfc       ! Local integer output status for namelist read 
     140      INTEGER ::   ios, ierr, icfc       ! Local integer 
    146141      !! 
    147142      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, & 
     
    154149      IF(lwp) WRITE(numout,*) 
    155150      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists' 
    156       IF(lwp) WRITE(numout,*) '~~~~~~~' 
     151      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    157152 
    158153      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    159154      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
    160 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    161  
     155901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    162156      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
    163157      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
    164 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
    165       IF(lwm) WRITE ( numont, namtrc ) 
     158902   IF( ios >  0 )  CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     159      IF(lwm) WRITE( numont, namtrc ) 
    166160 
    167161      ! Control settings 
     
    209203      ! 
    210204      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,*) ' ' 
     205         WRITE(numout,*) '   Namelist : namtrc' 
     206         WRITE(numout,*) '      Total number of passive tracers              jptra         = ', jptra 
     207         WRITE(numout,*) '      Total number of BGC tracers                  jp_bgc        = ', jp_bgc 
     208         WRITE(numout,*) '      Simulating PISCES model                      ln_pisces     = ', ln_pisces 
     209         WRITE(numout,*) '      Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc 
     210         WRITE(numout,*) '      Simulating water mass age                    ln_age        = ', ln_age 
     211         WRITE(numout,*) '      Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11 
     212         WRITE(numout,*) '      Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12 
     213         WRITE(numout,*) '      Simulating SF6 passive tracer                ln_sf6        = ', ln_sf6 
     214         WRITE(numout,*) '      Total number of CFCs tracers                 jp_cfc        = ', jp_cfc 
     215         WRITE(numout,*) '      Simulating C14   passive tracer              ln_c14        = ', ln_c14 
     216         WRITE(numout,*) '      Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
     217         WRITE(numout,*) '      Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
     218         WRITE(numout,*) '      Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
    228219      ENDIF 
    229220      ! 
     
    235226        ! 
    236227      ENDIF 
    237  
     228      ! 
    238229   END SUBROUTINE trc_nam_trc 
     230 
    239231 
    240232   SUBROUTINE trc_nam_trd 
     
    248240      !!                ( (PISCES, CFC, MY_TRC ) 
    249241      !!--------------------------------------------------------------------- 
    250  
    251242#if defined key_trdmxl_trc  || defined key_trdtrc 
    252       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    253       INTEGER ::  ierr 
     243      INTEGER  ::   ios, ierr                 ! Local integer 
    254244      !! 
    255245      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
     
    257247         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
    258248      !!--------------------------------------------------------------------- 
    259  
     249      ! 
    260250      IF(lwp) WRITE(numout,*) 
    261251      IF(lwp) WRITE(numout,*) 'trc_nam_trd : read the passive tracer diagnostics options' 
    262       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    263  
     252      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    264253      ! 
    265254      ALLOCATE( ln_trdtrc(jptra) )  
     
    267256      REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends 
    268257      READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905) 
    269 905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp ) 
    270  
     258905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp ) 
    271259      REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends 
    272260      READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 ) 
    273 906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp ) 
    274       IF(lwm) WRITE ( numont, namtrc_trd ) 
     261906   IF( ios >  0 )  CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp ) 
     262      IF(lwm) WRITE( numont, namtrc_trd ) 
    275263 
    276264      IF(lwp) THEN 
    277          WRITE(numout,*) 
    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 
     265         WRITE(numout,*) '   Namelist : namtrc_trd                    ' 
     266         WRITE(numout,*) '      frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc 
     267         WRITE(numout,*) '      control surface type              nn_ctls_trc            = ', nn_ctls_trc 
     268         WRITE(numout,*) '      restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart 
     269         WRITE(numout,*) '      instantantaneous or mean trends   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant 
     270         WRITE(numout,*) '      unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc 
    286271         DO jn = 1, jptra 
    287             IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn 
     272            IF( ln_trdtrc(jn) ) WRITE(numout,*) '      compute ML trends for tracer number :', jn 
    288273         END DO 
    289274      ENDIF 
     
    303288#endif 
    304289 
    305    !!---------------------------------------------------------------------- 
    306    !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    307    !! $Id$ 
    308    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    309290   !!====================================================================== 
    310291END MODULE trcnam 
Note: See TracChangeset for help on using the changeset viewer.