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/trcdta.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/trcdta.F90

    r9124 r9169  
    5555      !!              - allocates passive tracer data structure  
    5656      !!---------------------------------------------------------------------- 
    57       ! 
    58       INTEGER,INTENT(IN) :: ntrc                             ! number of tracers 
    59       INTEGER            :: jl, jn                           ! dummy loop indices 
    60       INTEGER            :: ierr0, ierr1, ierr2, ierr3       ! temporary integers 
    61       INTEGER            :: ios                              ! Local integer output status for namelist read 
    62       CHARACTER(len=100) :: clndta, clntrc 
    63       REAL(wp)           :: zfact 
    64       ! 
    65       CHARACTER(len=100)            :: cn_dir 
     57      INTEGER,INTENT(in) ::   ntrc   ! number of tracers 
     58      ! 
     59      INTEGER ::   jl, jn                            ! dummy loop indices 
     60      INTEGER ::   ios, ierr0, ierr1, ierr2, ierr3   ! local integers 
     61      REAL(wp) ::   zfact 
     62      CHARACTER(len=100) ::   clndta, clntrc 
     63      ! 
     64      CHARACTER(len=100) ::   cn_dir 
    6665      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i ! array of namelist informations on the fields to read 
    6766      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcdta 
     
    7271      ! 
    7372      IF( lwp ) THEN 
    74          WRITE(numout,*) ' ' 
    75          WRITE(numout,*) '  trc_dta_ini : Tracers Initial Conditions (IC)' 
    76          WRITE(numout,*) '  ~~~~~~~~~~~ ' 
     73         WRITE(numout,*) 
     74         WRITE(numout,*) 'trc_dta_ini : Tracers Initial Conditions (IC)' 
     75         WRITE(numout,*) '~~~~~~~~~~~ ' 
    7776      ENDIF 
    7877      ! 
     
    9190             n_trc_index(jn) = nb_trcdta  
    9291         ENDIF 
    93       ENDDO 
     92      END DO 
    9493      ! 
    9594      ntra = MAX( 1, nb_trcdta )   ! To avoid compilation error with bounds checking 
    9695      IF(lwp) THEN 
    97          WRITE(numout,*) ' ' 
    98          WRITE(numout,*) ' number of passive tracers to be initialize by data :', ntra 
    99          WRITE(numout,*) ' ' 
     96         WRITE(numout,*) 
     97         WRITE(numout,*) '   number of passive tracers to be initialize by data :', ntra 
    10098      ENDIF 
    10199      ! 
    102100      REWIND( numnat_ref )              ! Namelist namtrc_dta in reference namelist : Passive tracer input data 
    103101      READ  ( numnat_ref, namtrc_dta, IOSTAT = ios, ERR = 901) 
    104 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_ini in reference namelist', lwp ) 
    105  
     102901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_dta_ini in reference namelist', lwp ) 
    106103      REWIND( numnat_cfg )              ! Namelist namtrc_dta in configuration namelist : Passive tracer input data 
    107104      READ  ( numnat_cfg, namtrc_dta, IOSTAT = ios, ERR = 902 ) 
    108 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_ini in configuration namelist', lwp ) 
     105902   IF( ios >  0 )  CALL ctl_nam ( ios , 'namtrc_dta_ini in configuration namelist', lwp ) 
    109106      IF(lwm) WRITE ( numont, namtrc_dta ) 
    110107 
     
    121118                  &              ' differs from that of tracer : '//TRIM(clntrc)//' ') 
    122119               ENDIF 
    123                WRITE(numout,*) ' ' 
    124                WRITE(numout,'(a, i4,3a,e11.3)') ' Read IC file for tracer number :', & 
     120               WRITE(numout,*) 
     121               WRITE(numout,'(a, i4,3a,e11.3)') '   Read IC file for tracer number :', & 
    125122               &            jn, ', name : ', TRIM(clndta), ', Multiplicative Scaling factor : ', zfact 
    126123            ENDIF 
Note: See TracChangeset for help on using the changeset viewer.