!> \file util_recovery.f90 !! Module avec les routines d'initialisation et de test des sortie cptr ou nc !< !> \namespace util_recovery !! This module gathers routines to read and write cptr files !! \author BAYA Hassine !! \date Septembre 2010 !! @note Used module !! @note - use module3D_phy !< module util_recovery use module3D_phy implicit none double precision ,dimension(:),allocatable :: tab_time double precision :: dtout real*8, dimension(:), pointer :: time_out logical :: logic_out contains !> SUBROUTINE: init_recovery !! Initialise les sorties recovery pas de temps et temps de sortie !> subroutine init_recovery implicit none integer :: num_file = 22 integer :: i,j character (len=10) :: comment if (itracebug.eq.1) call tracebug(' Entree dans routine init_recovery ') !open(num_file,file='../SOURCES/Fichiers-parametres/TEMPS-CPTR-NC.dat') !open(num_file,file=trim(dirsource)//'/Fichiers-parametres/TEMPS-CPTR-NC.dat') open(num_file,file=trim(dirsource)//'/TEMPS-CPTR-NC.dat') ! passe les commentaires qui se terminent par une ligne de ~~~ comment1: do read(num_file,'(a10)') comment if (comment.eq.'~~~~~~~~~~') exit comment1 end do comment1 ! lecture de dtcpt read(num_file,*) dtout read(num_file,*) !saut de la ligne "-------" read(num_file,*) i if (.not. allocated(tab_time)) then ! aurel dec15 allocate(tab_time(i)) end if do j=1,i read(num_file,*) tab_time(j) end do comment2: do read(num_file,'(a10)') comment if (comment .eq. '----------') exit comment2 end do comment2 !fin de lecture close(num_file) return end subroutine init_recovery !> SUBROUTINE: testout_recovery !! Test si on effectue les sorties des fichiers de reprise !> subroutine testout_recovery(filin) implicit none real :: difftime integer :: indice integer :: ipredef character(len=*),intent(inout) :: filin character(len=10) :: ntime character(len=1) :: signe,unite if (itracebug.eq.1) call tracebug(' Entree dans routine testout_recovery ') if (.not.associated(time_out)) then allocate(time_out(1)) end if ipredef=0 logic_out=.FALSE. ! aurel, dec15. en plus des id avec des "k" etc. on va rajouter ! un identifiant "grestart" pour identifier ces .nc restarts ! des autres predef: do indice=1,size(tab_time) difftime=abs(TIME-tab_time(indice)) if ( difftime.lt.dtmin ) then ipredef=1 time_out(1)=tab_time(indice) exit predef end if end do predef if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR. & (ABS(TIME+297000).LT.dtmin) .OR. & (ABS(TIME+126000).LT.dtmin) .OR. & (ABS(TIME+21000) .LT.dtmin) .OR. & (ABS(TIME+16000) .LT.dtmin) .OR. & (TIME .EQ. TEND).OR.(ipredef.eq.1) ) THEN if (ipredef .EQ. 1) then ! pour changer de signe entre le passe et le futur if (tab_time(indice).GT.0.) then signe= '+' else signe= '-' endif if (int(mod(abs(tab_time(indice)),1000.)).eq.0) then ! temps multiple de 1000 unite='k' write(ntime,'(i10)') int(abs(tab_time(indice)/1000.)) else if (int(mod(abs(tab_time(indice)),100.)).eq.0) then ! temps multiple de 100 unite='c' write(ntime,'(i10)') int(abs(tab_time(indice)/100.)) else if (int(mod(abs(tab_time(indice)),10.)).eq.0) then ! temps multiple de 10 unite='d' write(ntime,'(i10)') int(abs(tab_time(indice)/10.)) else ! temps en annees unite='a' write(ntime,'(i10)') int(abs(tab_time(indice)/1.)) endif filin=runname//'-grestart'//signe//unite//trim(ADJUSTL(ntime)) else !ipredef==0 if (TIME .ge. Tend) then time_out(1)=TIME filin=runname//'-grestart_2' else time_out(1)=TIME filin=runname//'-grestart_1' end if end if logic_out=.TRUE. endif end subroutine testout_recovery end module util_recovery