Skip to content
Snippets Groups Projects
Commit 35277374 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 18/01/2023: bugfix: close backup files in the correct order for the...

Philippe 18/01/2023: bugfix: close backup files in the correct order for the first temporal iteration
This solves crash in case of model restart with balloons
parent 555f607a
No related branches found
No related tags found
No related merge requests found
...@@ -120,13 +120,17 @@ IMPLICIT NONE ...@@ -120,13 +120,17 @@ IMPLICIT NONE
! !
!* 0.1 declarations of local variables !* 0.1 declarations of local variables
! !
TYPE TFILEPTR
TYPE(TFILEDATA), POINTER :: TPFILE
END TYPE TFILEPTR
!
INTEGER :: JMODEL ! loop index INTEGER :: JMODEL ! loop index
INTEGER :: ITEMP_MODEL1 ! loop increment INTEGER :: ITEMP_MODEL1 ! loop increment
LOGICAL :: GEXIT ! flag for the end of the LOGICAL :: GEXIT ! flag for the end of the temporal loop
! temporal loop
INTEGER :: IINFO_ll ! return code of // routines INTEGER :: IINFO_ll ! return code of // routines
TYPE(TFILEDATA), POINTER :: TZBAKFILE ! Backup file TYPE(TFILEDATA), POINTER :: TZBAKFILE ! Backup file
TYPE(DATE_TIME) :: TZDTMODELN ! Date/time of current model computation TYPE(DATE_TIME) :: TZDTMODELN ! Date/time of current model computation
TYPE(TFILEPTR), DIMENSION(:), ALLOCATABLE :: TZBAKFILES ! Array of pointers to backup files
! !
#ifdef CPLOASIS #ifdef CPLOASIS
CHARACTER(LEN=28) :: CNAMELIST CHARACTER(LEN=28) :: CNAMELIST
...@@ -192,17 +196,27 @@ END IF ...@@ -192,17 +196,27 @@ END IF
!* 2. TEMPORAL LOOP !* 2. TEMPORAL LOOP
! ------------- ! -------------
! !
ALLOCATE( TZBAKFILES( NMODEL ) )
!
DO JMODEL=1,NMODEL DO JMODEL=1,NMODEL
CALL GO_TOMODEL_ll(JMODEL,IINFO_ll) CALL GO_TOMODEL_ll(JMODEL,IINFO_ll)
CALL GOTO_MODEL(JMODEL) CALL GOTO_MODEL(JMODEL)
CSTORAGE_TYPE='TT' CSTORAGE_TYPE='TT'
CALL MODEL_n( 1, TZBAKFILE, TZDTMODELN, GEXIT ) CALL MODEL_n( 1, TZBAKFILES(JMODEL)%TPFILE, TZDTMODELN, GEXIT )
END DO
!
! Close backup files
! This is done after previous loop because parent files must stay open for child files (ie to write balloon positions in restarts)
DO JMODEL = 1, NMODEL
TZBAKFILE => TZBAKFILES(JMODEL)%TPFILE
IF ( TZBAKFILE%LOPENED ) THEN IF ( TZBAKFILE%LOPENED ) THEN
CALL IO_FILE_CLOSE( TZBAKFILE, TPDTMODELN = TZDTMODELN ) CALL IO_FILE_CLOSE( TZBAKFILE, TPDTMODELN = TZDTMODELN )
NULLIFY( TZBAKFILE ) NULLIFY( TZBAKFILE )
END IF END IF
END DO END DO
! !
DEALLOCATE( TZBAKFILES )
!
IF(GEXIT) THEN IF(GEXIT) THEN
!callabortstop !callabortstop
CALL ABORT CALL ABORT
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment