-
Notifications
You must be signed in to change notification settings - Fork 3
/
write_restart.f90
executable file
·63 lines (53 loc) · 1.37 KB
/
write_restart.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
!***************************************************************
! 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: write_restart
!
! VERSION and DATE: MASS1 v0.6 10/8/97
!
! PURPOSE: write a binary file of the model values at the
! end of a simulation
!
! RETURNS:
!
! REQUIRED:
!
! LOCAL VARIABLES:
!
! COMMENTS: needs to be changed if an arbitrary link naming
! convention is allowed.
!
!
! MOD HISTORY:
!
!
!***************************************************************
!
SUBROUTINE write_restart
USE link_vars
USE general_vars
USE point_vars
USE file_vars
USE transport_vars
USE scalars
USE utility
IMPLICIT NONE
INTEGER :: link,point
INTEGER :: status
OPEN(fileunit(13),file=filename(13),form='unformatted', iostat=status)
IF (status .EQ. 0) THEN
CALL status_message('Writing hot start to ' // TRIM(filename(13)))
ELSE
CALL error_message(TRIM(filename(13)) // ': cannot open for writing', fatal=.TRUE.)
END IF
DO link=1,maxlinks
DO point=1,maxpoints(link)
WRITE(fileunit(13))link,point,q(link,point),y(link,point),species(1)%conc(link,point),species(2)%conc(link,point)
END DO
END DO
CLOSE(fileunit(13))
END SUBROUTINE write_restart