Ignore:
Timestamp:
01/21/08 14:44:35 (17 years ago)
Author:
bellier
Message:

calendar :

  • modification of tests to get rid of a truncation error in the determination of the date change.
  • addition in "itau2ymds" of a message to inform usage of undefined elements (call with "ioconf_startdate" not done)

restcom :

  • some orthographic correction

JB

File:
1 edited

Legend:

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

    r122 r236  
    3737!- 
    3838  INTEGER,PARAMETER :: & 
    39  &  max_var=200, max_file=50, max_dim=NF90_MAX_VAR_DIMS 
     39 &  max_var=500, max_file=50, max_dim=NF90_MAX_VAR_DIMS 
    4040!- 
    4141  CHARACTER(LEN=9),SAVE :: calend_str='unknown' 
     
    4545!- 
    4646  INTEGER,SAVE :: nbfiles = 0  
    47   INTEGER,SAVE :: netcdf_id(max_file,2) = -1 
     47  INTEGER,DIMENSION(max_file,2),SAVE :: netcdf_id = -1 
    4848!- 
    4949! Description of the content of the 'in' files and the 'out' files. 
     
    6767! Time step and time origine in the input file. 
    6868!- 
    69   REAL,SAVE :: deltat(max_file), timeorig(max_file) 
     69  REAL,DIMENSION(max_file),SAVE :: deltat,timeorig 
    7070!- 
    7171! Description of the axes in the output file 
     
    7474!   itau_out  : Time step which is written on this index of the file 
    7575!- 
    76   INTEGER,SAVE :: tstp_out(max_file) 
    77   INTEGER,SAVE :: itau_out(max_file) 
     76  INTEGER,DIMENSION(max_file),SAVE :: tstp_out,itau_out 
    7877!- 
    7978! Description of the axes in the output file 
    8079!- 
     80! For the ?ax_infs variable the following order is used : 
     81!   ?ax_infs (if,in,1) = size of axis 
     82!   ?ax_infs (if,in,2) = id of dimension 
    8183! Number of x,y and z axes in the output file :  
    8284!   ?ax_nb(if) 
    83 ! For the ?ax_infs variable the following order is used : 
    84 !   ?ax_infs (if, in,1) = size of axis 
    85 !   ?ax_infs (if, in,2) = id of dimension 
    86 !- 
    87   INTEGER,SAVE :: & 
    88  &  xax_infs(max_file,max_dim,2), yax_infs(max_file,max_dim,2),& 
    89  &  zax_infs(max_file,max_dim,2), qax_infs(max_file,max_dim,2) 
    90   INTEGER,SAVE :: & 
    91  &  xax_nb(max_file)=0, yax_nb(max_file)=0, & 
    92  &  zax_nb(max_file)=0, qax_nb(max_file)=0 
     85!- 
     86  INTEGER,DIMENSION(max_file,max_dim,2),SAVE :: & 
     87 &  xax_infs,yax_infs,zax_infs 
     88  INTEGER,DIMENSION(max_file),SAVE :: & 
     89 &  xax_nb=0,yax_nb=0,zax_nb=0 
    9390!- 
    9491! Description of the time axes in the input and output files 
     
    656653  INTEGER :: ncfid,iret,it,iax,iv,tszij 
    657654  INTEGER,ALLOCATABLE :: tmp_index(:,:) 
    658   REAL,ALLOCATABLE  :: tmp_julian(:,:) 
    659   CHARACTER(LEN=80)  :: itau_orig,tax_orig,calendar 
     655  REAL,ALLOCATABLE :: tmp_julian(:,:) 
     656  CHARACTER(LEN=80) :: itau_orig,tax_orig,calendar 
    660657  CHARACTER(LEN=9) :: tmp_cal 
    661658  INTEGER :: year0,month0,day0,hours0,minutes0,seci 
    662   REAL ::sec0,un_jour,un_an,date0_ju,ttmp 
     659  REAL :: sec0,un_jour,un_an,date0_ju,ttmp 
    663660  CHARACTER :: strc 
    664661!- 
     
    718715    itau_orig = & 
    719716      itau_orig(INDEX(itau_orig,'since')+6:LEN_TRIM(itau_orig)) 
    720     iret = NF90_GET_ATT & 
    721  &           (ncfid,tind_varid_in(fid),'tstep_sec',timestep) 
    722 !--- 
    723 !-- This time origine will dominate as it is linked to the time steps. 
     717    iret = & 
     718 &    NF90_GET_ATT(ncfid,tind_varid_in(fid),'tstep_sec',timestep) 
     719!--- 
     720!-- This time origin will dominate as it is linked to the time steps. 
    724721!--- 
    725722    READ (UNIT=itau_orig,FMT='(I4.4,5(a,I2.2))') & 
     
    16621659    IF (zax_infs(fid,1,1) > 0) req_sz = req_sz*zax_infs(fid,1,1) 
    16631660  ELSE 
    1664     CALL ipslerr (3,'resput_opp_r1d', & 
     1661    CALL ipslerr (3,'restput_opp_r1d', & 
    16651662      'Unable to performe an operation on this variable as it has', & 
    16661663      'a second and third dimension',vname_q) 
     
    17111708       scal,req_sz,buff_tmp2) 
    17121709  ELSE 
    1713     CALL ipslerr (3,'resput_opp_r1d', & 
     1710    CALL ipslerr (3,'restput_opp_r1d', & 
    17141711      'The operation you wish to do on the variable for the ', & 
    17151712       & 'restart file is not allowed.',topp) 
     
    17651762    IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1) 
    17661763  ELSE 
    1767     CALL ipslerr (3,'resput_opp_r2d', & 
     1764    CALL ipslerr (3,'restput_opp_r2d', & 
    17681765      'Unable to performe an operation on this variable as it has', & 
    17691766      'a second and third dimension',vname_q) 
     
    17711768!- 
    17721769  IF (jjm < 1) THEN 
    1773     CALL ipslerr (3,'resput_opp_r2d', & 
     1770    CALL ipslerr (3,'restput_opp_r2d', & 
    17741771      'Please specify a second dimension which is the', & 
    17751772      'layer on which the operations are performed',vname_q) 
     
    18241821    ENDDO 
    18251822  ELSE 
    1826     CALL ipslerr (3,'resput_opp_r2d', & 
     1823    CALL ipslerr (3,'restput_opp_r2d', & 
    18271824      'The operation you wish to do on the variable for the ', & 
    18281825      'restart file is not allowed.',topp) 
Note: See TracChangeset for help on using the changeset viewer.