Ignore:
Timestamp:
12/16/19 14:33:26 (4 years ago)
Author:
jgipsl
Message:

Following changes have been done by A.Jornet/LSCE. No change is results and no change in usage have been seen. Some more error checking might stop the model for example if dimensions are not correct in call to histcom module.

Restcom:

  • Define a new var size length (20 to 100 )→ pbs found without no errors
  • Raise an error when var name is too long
  • Deallocate any buffer at the end of all restput/restcget calls → buffers only increase size. After loading/saving nothing is done with this memory

Histcom:

  • Raise an error if given history declared variables do not match with given dimensions from histwrite

getincom and stringop:

  • Enable any length character for the run.def → useful for long filepaths

flincom

  • Enable filenames longer than 80 chars to any
  • Deallocate buffers at the end of any flinget subroutine
File:
1 edited

Legend:

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

    r3474 r4863  
    691691  INTEGER :: iv, lll 
    692692  INTEGER :: xid, yid, zid, tid 
    693   CHARACTER(LEN=80) :: name 
     693  CHARACTER(LEN=:), ALLOCATABLE :: name 
    694694  CHARACTER(LEN=30) :: axname 
    695695!- 
     
    999999  ENDDO 
    10001000!------------------------- 
     1001  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    10011002END SUBROUTINE flinget_r1d 
    10021003!- 
     
    10411042  ENDDO 
    10421043!------------------------- 
     1044  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    10431045END SUBROUTINE flinget_r2d 
    10441046!- 
     
    10831085    ENDDO 
    10841086  ENDDO 
     1087  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    10851088!-------------------------------- 
    10861089END SUBROUTINE flinget_r2d_zoom2d 
     
    11281131  ENDDO 
    11291132!------------------------- 
     1133  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    11301134END SUBROUTINE flinget_r3d 
    11311135!- 
     
    11731177  ENDDO 
    11741178!-------------------------------- 
     1179  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    11751180END SUBROUTINE flinget_r3d_zoom2d 
    11761181!- 
     
    12191224  ENDDO 
    12201225!------------------------- 
     1226  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    12211227END SUBROUTINE flinget_r4d 
    12221228!- 
     
    12661272  ENDDO 
    12671273!-------------------------------- 
     1274  IF (ALLOCATED(buff_tmp)) DEALLOCATE(buff_tmp) 
    12681275END SUBROUTINE flinget_r4d_zoom2d 
    12691276!- 
Note: See TracChangeset for help on using the changeset viewer.