Changeset 236 for IOIPSL/trunk/src/restcom.f90
- Timestamp:
- 01/21/08 14:44:35 (17 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
IOIPSL/trunk/src/restcom.f90
r122 r236 37 37 !- 38 38 INTEGER,PARAMETER :: & 39 & max_var= 200, max_file=50, max_dim=NF90_MAX_VAR_DIMS39 & max_var=500, max_file=50, max_dim=NF90_MAX_VAR_DIMS 40 40 !- 41 41 CHARACTER(LEN=9),SAVE :: calend_str='unknown' … … 45 45 !- 46 46 INTEGER,SAVE :: nbfiles = 0 47 INTEGER, SAVE :: netcdf_id(max_file,2)= -147 INTEGER,DIMENSION(max_file,2),SAVE :: netcdf_id = -1 48 48 !- 49 49 ! Description of the content of the 'in' files and the 'out' files. … … 67 67 ! Time step and time origine in the input file. 68 68 !- 69 REAL, SAVE :: deltat(max_file), timeorig(max_file)69 REAL,DIMENSION(max_file),SAVE :: deltat,timeorig 70 70 !- 71 71 ! Description of the axes in the output file … … 74 74 ! itau_out : Time step which is written on this index of the file 75 75 !- 76 INTEGER,SAVE :: tstp_out(max_file) 77 INTEGER,SAVE :: itau_out(max_file) 76 INTEGER,DIMENSION(max_file),SAVE :: tstp_out,itau_out 78 77 !- 79 78 ! Description of the axes in the output file 80 79 !- 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 81 83 ! Number of x,y and z axes in the output file : 82 84 ! ?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 93 90 !- 94 91 ! Description of the time axes in the input and output files … … 656 653 INTEGER :: ncfid,iret,it,iax,iv,tszij 657 654 INTEGER,ALLOCATABLE :: tmp_index(:,:) 658 REAL,ALLOCATABLE 659 CHARACTER(LEN=80) ::itau_orig,tax_orig,calendar655 REAL,ALLOCATABLE :: tmp_julian(:,:) 656 CHARACTER(LEN=80) :: itau_orig,tax_orig,calendar 660 657 CHARACTER(LEN=9) :: tmp_cal 661 658 INTEGER :: year0,month0,day0,hours0,minutes0,seci 662 REAL :: sec0,un_jour,un_an,date0_ju,ttmp659 REAL :: sec0,un_jour,un_an,date0_ju,ttmp 663 660 CHARACTER :: strc 664 661 !- … … 718 715 itau_orig = & 719 716 itau_orig(INDEX(itau_orig,'since')+6:LEN_TRIM(itau_orig)) 720 iret = NF90_GET_ATT&721 & 722 !--- 723 !-- This time origin ewill 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. 724 721 !--- 725 722 READ (UNIT=itau_orig,FMT='(I4.4,5(a,I2.2))') & … … 1662 1659 IF (zax_infs(fid,1,1) > 0) req_sz = req_sz*zax_infs(fid,1,1) 1663 1660 ELSE 1664 CALL ipslerr (3,'res put_opp_r1d', &1661 CALL ipslerr (3,'restput_opp_r1d', & 1665 1662 'Unable to performe an operation on this variable as it has', & 1666 1663 'a second and third dimension',vname_q) … … 1711 1708 scal,req_sz,buff_tmp2) 1712 1709 ELSE 1713 CALL ipslerr (3,'res put_opp_r1d', &1710 CALL ipslerr (3,'restput_opp_r1d', & 1714 1711 'The operation you wish to do on the variable for the ', & 1715 1712 & 'restart file is not allowed.',topp) … … 1765 1762 IF (yax_infs(fid,1,1) > 0) req_sz = req_sz*yax_infs(fid,1,1) 1766 1763 ELSE 1767 CALL ipslerr (3,'res put_opp_r2d', &1764 CALL ipslerr (3,'restput_opp_r2d', & 1768 1765 'Unable to performe an operation on this variable as it has', & 1769 1766 'a second and third dimension',vname_q) … … 1771 1768 !- 1772 1769 IF (jjm < 1) THEN 1773 CALL ipslerr (3,'res put_opp_r2d', &1770 CALL ipslerr (3,'restput_opp_r2d', & 1774 1771 'Please specify a second dimension which is the', & 1775 1772 'layer on which the operations are performed',vname_q) … … 1824 1821 ENDDO 1825 1822 ELSE 1826 CALL ipslerr (3,'res put_opp_r2d', &1823 CALL ipslerr (3,'restput_opp_r2d', & 1827 1824 'The operation you wish to do on the variable for the ', & 1828 1825 'restart file is not allowed.',topp)
Note: See TracChangeset
for help on using the changeset viewer.