Ignore:
Timestamp:
Dec 1, 2022, 6:56:48 PM (19 months ago)
Author:
dcugnet
Message:

Cleaning: remove unused variables

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/misc/strings_mod.F90

    r4358 r4363  
    4949SUBROUTINE init_printout(lunout_, prt_level_)
    5050  INTEGER, INTENT(IN) :: lunout_, prt_level_
    51   lunout = lunout_
     51  lunout    = lunout_
     52  prt_level = prt_level_
    5253END SUBROUTINE init_printout
    5354!==============================================================================================================================
     
    457458  LOGICAL, OPTIONAL, INTENT(IN)  :: lSc                              !--- Care about nbs with front sign or in scient. notation
    458459!------------------------------------------------------------------------------------------------------------------------------
    459   INTEGER               :: idx0                                      !--- Used to display an identified non-numeric string
    460   INTEGER, ALLOCATABLE  :: ii(:)
    461   LOGICAL               :: ll, ls
    462   CHARACTER(LEN=maxlen) :: d
     460  INTEGER :: idx0                                                    !--- Used to display an identified non-numeric string
    463461  lerr = .FALSE.
    464462  idx = strIdx1(rawList, del, ibeg, idel)                            !--- idx/=0: del(idel) is at position "idx" in "rawList"
     
    681679  LOGICAL, OPTIONAL, INTENT(IN)    :: lsurr      !--- TRUE => key must be surrounded by special characters to be substituted
    682680!------------------------------------------------------------------------------------------------------------------------------
    683   CHARACTER(LEN=1024) :: s, t
    684681  INTEGER :: i0, ix, nk, ns
    685682  LOGICAL :: lsur, lb, le
     
    11811178  CHARACTER(LEN=maxlen)                   :: mes, sub, fm='(f12.9)', prf
    11821179  CHARACTER(LEN=maxlen),      ALLOCATABLE :: ttl(:), vnm(:)
    1183   LOGICAL,                    ALLOCATABLE :: m(:)
    11841180  INTEGER,                    ALLOCATABLE :: ki(:), kj(:), kl(:)
    1185   INTEGER                                 :: i, j, k, rk, ib, ie, itr, nm, nv, unt, nRmx, nCmx, nHd, rk1
     1181  INTEGER                                 :: i, j, k, rk, nv, unt, nRmx, nCmx, nHd
    11861182  REAL,                       ALLOCATABLE :: val(:,:)
    11871183
     
    11991195  lerr= SIZE(a,1) /= PRODUCT(n); IF(fmsg('profile "n" does not match "a" and "ll"', sub, lerr, unt)) RETURN
    12001196
    1201   SELECT CASE(rk1)                                                   !--- Indices list
     1197  SELECT CASE(rk)                                                   !--- Indices list
    12021198    CASE(0); IF(ll(1)) THEN; WRITE(unt,'(a,", ",a," = ",2f12.9)')TRIM(vnm(1)),TRIM(vnm(2)),a(1,1),a(1,2); RETURN; END IF
    12031199    CASE(1); ki = [  (i,i=1,n(1)) ]
Note: See TracChangeset for help on using the changeset viewer.