-
Notifications
You must be signed in to change notification settings - Fork 3
/
read_hotstart.f90
executable file
·69 lines (58 loc) · 1.46 KB
/
read_hotstart.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
!***************************************************************
! Copyright (c) 2017 Battelle Memorial Institute
! Licensed under modified BSD License. A copy of this license can be
! found in the LICENSE file in the top level directory of this
! distribution.
!***************************************************************
!
! NAME: read_hotstart
!
! VERSION and DATE: MASS1 v0.6 10/8/97
!
! PURPOSE:reads a binary hotstart file to start model run from
! a previous saved restart file.
!
! RETURNS:
!
! REQUIRED:
!
! LOCAL VARIABLES:
!
! COMMENTS:
!
!
! MOD HISTORY:
!
!
!***************************************************************
!
SUBROUTINE read_hotstart
USE utility
USE link_vars
USE general_vars
USE point_vars
USE file_vars
USE transport_vars
USE scalars
IMPLICIT NONE
INTEGER :: link,point,i,j
LOGICAL :: file_exist
!OPEN(91,file='hotstart.dat',form='binary')
INQUIRE(FILE=filename(12),EXIST=file_exist)
IF(file_exist)THEN
OPEN(fileunit(12),file=filename(12),form='unformatted')
WRITE(99,*)'hotstart file opened: ',filename(12)
ELSE
WRITE(*,*)'hotstart file does not exist - ABORT: ',filename(12)
WRITE(99,*)'hotstart file does not exist - ABORT: ',filename(12)
CALL EXIT(1)
ENDIF
DO link=1,maxlinks
DO point=1,maxpoints(link)
READ(fileunit(12))i,j,q(link,point),y(link,point),species(1)%conc(link,point),species(2)%conc(link,point)
END DO
END DO
lateral_inflow = 0.0
lateral_inflow_old = 0.0
CLOSE(fileunit(12))
END SUBROUTINE read_hotstart