-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathm_store.f90
129 lines (117 loc) · 2.7 KB
/
m_store.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
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
!----------------------------------------------------------------------
! MELQUIADES: Metropolis Monte Carlo Program !
!----------------------------------------------------------------------
!bop
!
! !Module: m_store
!
! !Description: This modules contains a routine for writting:
!1) A like-formatted simulation box file;
!2) A file in conventional xyz file format.
!\\
!\\
! !Interface:
!
module m_store
!
! !Uses:
use m_kind
use m_simtype
use m_boxtype
use m_unit
!
! !Public member functions:
!
private
public :: r_saves
public :: r_newbox
!
! !Revision history:
! 08Aug 2015 Asdrubal Lozada
!
!eop
!----------------------------------------------------------------------
contains
!
!bop
!
! !Iroutine: r_saves
!
! !Description: This routine made a format xyz file
!\\
!\\
! !Interface:
subroutine r_saves(energy, virial, y, x )
!
implicit none
!
! !Input parameters:
type(simulation), intent(inout) :: y
type(box), pointer :: x
real(rkind), intent(inout) :: energy
real(rkind), intent(inout) :: virial
!
! !Revision history
! 08Aug 2015 Asdrubal Lozada
!
!eop
!----------------------------------------------------------------------
! Local variables
integer :: j, i
character(len=2) :: label
real(rkind) :: xx,yy,zz
character(len=10) :: ival, rkval
character(len=10) :: caption
caption = 'Energy = '
write(ival,'(i10)') y%m_mxatms
write(rkval,'(f10.1)') energy
write(ixyz,'(a10)') adjustl(ival)
write(ixyz,'(2a10)') caption, adjustl(rkval)
do j = 1, y%m_mxmol
do i = 1, x%m_ns(j)
label = x%m_symbol(i,j)
xx = x%m_site(1,i,j) + x%m_cmass(1,j)
yy = x%m_site(2,i,j) + x%m_cmass(2,j)
zz = x%m_site(3,i,j) + x%m_cmass(3,j)
write(ixyz,'(a2,2x,f10.5,2x,f10.5,2x,f10.5)')label,xx,yy,zz
end do
end do
end subroutine r_saves
!
!bop
!
! !Iroutine: r_newbox
!
! !Description: This routine update boxfile at the end of Markov chain.
!\\
!\\
!
! !Interface:
subroutine r_newbox( y, x )
!
! !Input parameters:
type(simulation), intent(inout) :: y
type(box), pointer :: x
!
! !Revision history:
! 08Aug 2015 Asdrubal Lozada
!
!eop
!----------------------------------------------------------------------
! Local Variable
integer :: i, j
character(len=40) :: line
line = trim(y%m_boxfile)
open(inbox, file=line, status='old')
rewind(inbox)
write(inbox,*) y%m_ntf
write(inbox,*) x%m_nmol(:), x%m_nsite(:), x%m_mass(:), x%m_edge(:)
write(inbox,*) m_seed
do j = 1, y%m_mxmol
write(inbox,*) trim(x%m_molname(j)), x%m_idtype(j), x%m_cmass(:,j)
do i = 1, x%m_ns(j)
write(inbox,*) x%m_symbol(i,j), x%m_idpar(i,j), x%m_site(:,i,j)
end do
end do
end subroutine r_newbox
end module m_store