forked from atoms-ufrj/postlammps
-
Notifications
You must be signed in to change notification settings - Fork 0
/
mProp_List.f90
162 lines (145 loc) · 6.11 KB
/
mProp_List.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
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
!> This module define a classes for storage and management of property names and dimensions.
!!
!! @author Charlles R. A. Abreu ([email protected])
!! @date Sept 21, 2013
! This file is part of Postlammps.
!
! Postlammps is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! Postlammps is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with Postlammps. If not, see <http://www.gnu.org/licenses/>.
module mProp_List
use mConstants
implicit none
!> A structured type for storing and managing property names:
type Prop_List
!> The number of properties in the list.
integer :: Number = 0
!> The names of the properties in the list.
character(sl), allocatable :: Name(:)
!> The dimension of each property in the list.
integer, allocatable :: Dim(:)
!> The sum of dimensions of the properties in the list.
integer :: Total = 0
!> The initial position of each property in a contiguous array of data.
integer, allocatable :: First(:)
!> The final position of each property in a contiguous array of data.
integer, allocatable :: Last(:)
!> A character to be used as separator of property names. Default = " " (space).
character :: separator = " "
contains
procedure, private :: Prop_List_Add_Scalar
procedure, private :: Prop_List_Add_Array
!> Adds a new property or an array of new properties to the list.
!! @param[in] Name (string scalar/array) name of each new property to be added.
!! @param[in] Dim (integer scalar/array, optional) dimension of each new property to be added
!! (Default = 1 for each property).
generic :: Add => Prop_List_Add_Scalar, Prop_List_Add_Array
!> Returns a string with the names of the properties in the list.
!! @param[in] begin (string, optional) a heading string. Default = "" (none).
!! @param[in] middle (string, optional) a separation string. Default = Prop_List::separator.
!! @param[in] end (string, optional) a trailing string. Default = "" (none).
procedure :: Titles => Prop_List_Titles
!! Sums the values of all dimensions of each property.
!! @param[in] data (real array) an array with dimension Prop_List::Total.
!! @returns an array with dimension Prop_List::Number with the sums over dimensions of each
!! property.
procedure :: Sum => Prop_List_Sum
end type Prop_List
private :: Prop_List_Add_Scalar, Prop_List_Add_Array, Prop_List_Titles, Prop_List_Sum
contains
!-------------------------------------------------------------------------------------------------
subroutine Prop_List_Add_Scalar( a, Name, Dim )
class(Prop_List), intent(inout) :: a
character(*), intent(in) :: Name
integer, intent(in), optional :: Dim
if (present(Dim)) then
call Prop_List_Add_Array( a, [Name], [Dim] )
else
call Prop_List_Add_Array( a, [Name] )
end if
end subroutine Prop_List_Add_Scalar
!-------------------------------------------------------------------------------------------------
subroutine Prop_List_Add_Array( a, Name, Dim )
class(Prop_List), intent(inout) :: a
character(*), intent(in) :: Name(:)
integer, intent(in), optional :: Dim(:)
integer :: i
character(sl) :: caux(a%Number + size(Name))
integer :: iaux(a%Number + size(Name))
caux(1:a%Number) = a%Name
iaux(1:a%Number) = a%Dim
forall(i=1:size(Name)) caux(a%Number+i) = trim(adjustl(Name(i)))
if (present(Dim)) then
iaux(a%Number+1:size(iaux)) = Dim
else
iaux(a%Number+1:size(iaux)) = 1
end if
a%Number = a%Number + size(Name)
if (allocated(a%Name)) deallocate(a%Name,a%Dim,a%First,a%Last)
allocate( a%Name(a%Number), a%Dim(a%Number), a%First(a%Number), a%Last(a%Number) )
a%Name = caux
a%Dim = iaux
forall (i=1:a%Number)
a%First(i) = sum(a%Dim(1:i-1)) + 1
a%Last(i) = sum(a%Dim(1:i))
end forall
a%Total = a%Last(a%Number)
end subroutine Prop_List_Add_Array
!-------------------------------------------------------------------------------------------------
function Prop_List_Titles( Props, begin, middle, end ) result( Titles )
class(Prop_List), intent(inout) :: Props
character(*), intent(in), optional :: begin, middle, end
character(sl) :: Titles
character(10) :: C
integer :: i, j, k, n
if (present(begin)) then
Titles = begin
n = len(begin)
else
Titles = ""
n = 0
end if
k = 0
do i = 1, props%Number
do j = 1, props%Dim(i)
Titles = Titles(1:n)//trim(props%Name(i))
n = n + len_trim(props%Name(i))
if (props%Dim(i) > 1) then
write(C,'(I10)') j
C = adjustl(C)
Titles = Titles(1:n)//"["//trim(C)//"]"
n = n + len_trim(C) + 2
end if
k = k + 1
if (k < props%Total) then
if (present(middle)) then
Titles = Titles(1:n)//middle
n = n + len(middle)
else
Titles = Titles(1:n)//props%separator
n = n + 1
end if
end if
end do
end do
if (present(end)) Titles = Titles(1:n)//end
end function Prop_List_Titles
!-------------------------------------------------------------------------------------------------
function Prop_List_Sum( Props, Data ) result( S )
class(Prop_List), intent(in) :: Props
real(rb), intent(in) :: Data(Props%Total)
real(rb) :: S(Props%Number)
integer :: i
forall (i=1:Props%Number) S(i) = sum(Data(Props%First(i):Props%Last(i)))
end function Prop_List_Sum
!-------------------------------------------------------------------------------------------------
end module mProp_List