Ignore:
Timestamp:
03/24/10 16:34:25 (14 years ago)
Author:
bellier
Message:

histcom : securize histsync and histclo
fliocom : change argument name of fliocrfd for back compatibility

File:
1 edited

Legend:

Unmodified
Added
Removed
  • IOIPSL/trunk/src/fliocom.f90

    r940 r957  
    6262!! which contains the dimensions needed. 
    6363!! 
    64 !! SUBROUTINE fliocrfd (f_n,f_d_n,f_d_l,f_i,id_dom,cmode,c_f_n) 
     64!! SUBROUTINE fliocrfd (f_n,f_d_n,f_d_l,f_i,id_dom,mode,c_f_n) 
    6565!! 
    6666!! INPUT 
     
    8686!!              This argument can be equal to FLIO_DOM_DEFAULT 
    8787!!              (see "flio_dom_defset"). 
    88 !! (C) cmode  : String of (case insensitive) blank-separated words 
     88!! (C) mode   : String of (case insensitive) blank-separated words 
    8989!!              defining the mode used to create the file. 
    9090!!              Supported keywords : REPLACE, 32, 64 
     
    837837!- 
    838838!=== 
    839 SUBROUTINE fliocrfd (f_n,f_d_n,f_d_l,f_i,id_dom,cmode,c_f_n) 
     839SUBROUTINE fliocrfd (f_n,f_d_n,f_d_l,f_i,id_dom,mode,c_f_n) 
    840840!--------------------------------------------------------------------- 
    841841  IMPLICIT NONE 
     
    846846  INTEGER,INTENT(OUT) :: f_i 
    847847  INTEGER,OPTIONAL,INTENT(IN) :: id_dom 
    848   CHARACTER(LEN=*),OPTIONAL,INTENT(IN) :: cmode 
     848  CHARACTER(LEN=*),OPTIONAL,INTENT(IN) :: mode 
    849849  CHARACTER(LEN=*),OPTIONAL,INTENT(OUT) :: c_f_n 
    850850!- 
     
    897897  i_opt(:)=-1 
    898898!- 
    899   IF (PRESENT(cmode)) THEN 
     899  IF (PRESENT(mode)) THEN 
    900900!--- 
    901     IF (LEN_TRIM(cmode) > l_string) THEN 
     901    IF (LEN_TRIM(mode) > l_string) THEN 
    902902      CALL ipslerr (3,'fliocrfd', & 
    903  &     '"cmode" argument','too long','to be treated') 
    904     ENDIF 
    905     c_string = cmode(:) 
     903 &     '"mode" argument','too long','to be treated') 
     904    ENDIF 
     905    c_string = mode(:) 
    906906    CALL strlowercase (c_string) 
    907907!--- 
Note: See TracChangeset for help on using the changeset viewer.