Ignore:
Timestamp:
11/20/17 14:26:40 (6 years ago)
Author:
jgipsl
Message:
  • Added exit in flinget if error when reading values from file
  • Added possiblilty to use netcdf compression in restcom. Option is activated by adding optional argument use_compression when calling restini

Modifications done by A. Jornet-Puig, LSCE

File:
1 edited

Legend:

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

    r1932 r3474  
    16131613             start=w_sta(:), count=w_len(:)) 
    16141614!--- 
     1615    IF (iret /= NF90_NOERR) THEN 
     1616        WRITE(ipslout,*) 'flinget_mat 2.9 : ',NF90_STRERROR (iret) 
     1617        CALL ipslerr(3, 'flinget_mat','Error on netcdf NF90_GET_VAR','', '') 
     1618    ENDIF 
     1619!--- 
    16151620    itau_len=itau_fin-itau_dep+1 
    16161621    IF (l_dbg) WRITE(ipslout,*) 'flinget_mat 3.0 : clen, itau_len ',clen,itau_len 
     
    16311636    iret = NF90_GET_VAR (fid, vid, var, & 
    16321637             start=w_sta(:), count=w_len(:)) 
    1633   ENDIF 
    1634 !- 
    1635   IF (l_dbg) WRITE(ipslout,*) 'flinget_mat 3.1 : ',NF90_STRERROR (iret) 
     1638 
     1639    IF (iret /= NF90_NOERR) THEN 
     1640        WRITE(ipslout,*) 'flinget_mat 3.1 : ',NF90_STRERROR (iret) 
     1641        CALL  ipslerr(3, 'flinget_mat','Error on netcdf NF90_GET_VAR','Read in netcdf failed', '') 
     1642    ENDIF 
     1643  ENDIF 
     1644!- 
     1645  IF (l_dbg) WRITE(ipslout,*) 'flinget_mat 3.2 : ',NF90_STRERROR (iret) 
    16361646!-------------------------- 
    16371647END  SUBROUTINE flinget_mat 
Note: See TracChangeset for help on using the changeset viewer.