-
Notifications
You must be signed in to change notification settings - Fork 0
/
quit.f90
executable file
·102 lines (84 loc) · 3.04 KB
/
quit.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! !
! FILE: QuitRoutine.F90 !
! CONTAINS: subroutine QuitRoutine, NotifyError !
! !
! PURPOSE: Routines to exit the program and write the !
! data if necessary !
! !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine QuitRoutine(tin,normalexit,errorcode)
use hdf5
use mpih
use param
!use coll_mod !KZ: no collisions for now
implicit none
logical, intent(in) :: normalexit
integer :: errorcode
real :: tin(3)
if(errorcode.ne.100) then !EP skip if already finalized
tin(3) = MPI_WTIME()
if(ismaster) write(6,'(a,f10.2,a)') 'Total Iteration Time = ',tin(3) -tin(2),' sec.'
if(ismaster) then
call NotifyError(errorcode)
endif
if(normalexit) then
! call WriteStats
call mpi_write_continua
!call WriteRandForcCoef
call continua_particle
!call continua_collision
if(ismaster) write(6,'(a)') 'Continuation files written'
else
call MpiAbort
endif
call dfftw_destroy_plan(fwd_plan)
call dfftw_destroy_plan(bck_plan)
call HdfClose
if(ismaster) then
open(27,file="flowmov/Total_time.out")
write(27,*)"Total simulation time in sec.: ", tin(3)-tin(1)
close(27)
endif
call mem_dealloc
call dealloc_trigeo
if (specflag) call dealloc_spec
call FinalizeMPI
endif
end subroutine QuitRoutine
!====================================================================================
subroutine NotifyError(errorcode)
use param
implicit none
integer, intent(in) :: errorcode
real :: qmax
if(errorcode.eq.166) then
write(6,168) dt
168 format(10x,'dt too small, DT= ',e14.7)
else if(errorcode.eq.165) then
write(6,164)
164 format(10x,'cfl too large ')
else if(errorcode.eq.266) then
write(6,268)
268 format(10x,'velocities diverged')
else if(errorcode.eq.169) then
write(6,178)
write(6,179)
write(6,180)
178 format(10x,'too large local residue for mass conservation at:')
179 format(10x,'Probably the matrix in SolvePressureCorrection')
180 format(10x,'is singular. Try changing nxm or str3')
call divgck(qmax)
else if(errorcode.eq.333) then
write(*,*) "time greater than tmax"
write(*,*) "statistics and continuation updated"
else if(errorcode.eq.334) then
write(*,*) "walltime greater than walltimemax"
write(*,*) "statistics and continuation updated"
else if(errorcode.eq.444) then
write(*,*) "FFT size in ny or nz is not efficient"
else
write(*,*) "Maximum number of timesteps reached"
end if
return
end