-
Notifications
You must be signed in to change notification settings - Fork 0
/
CharacterArray.f90
80 lines (58 loc) · 2.35 KB
/
CharacterArray.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
! '''
! Neuromuscular simulator in Python.
! Copyright (C) 2018 Renato Naville Watanabe
! This program 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
! any later version.
! This program 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 this program. If not, see <http://www.gnu.org/licenses/>.
! Contact: renato.watanabe@ufabc.edu.br
! '''
module CharacterArrayClass
use StringClass
implicit none
private
public :: CharacterArray
type CharacterArray
type(String), dimension(:), allocatable :: item
contains
procedure :: AddToList
end type CharacterArray
interface CharacterArray
module procedure init_CharacterArray
end interface CharacterArray
contains
type (CharacterArray) function init_CharacterArray()
if (allocated(init_CharacterArray%item)) then
deallocate(init_CharacterArray%item)
end if
end function
subroutine AddToList(self, newString)
class(CharacterArray), intent(inout) :: self
character(*), intent(in) :: newString
type(CharacterArray) :: clist
integer :: isize, i
clist = CharacterArray()
if(allocated(self%item)) then
isize = size(self%item)
allocate(clist%item(isize+1))
do i=1,isize
clist%item(i) = self%item(i)
end do
clist%item(isize+1) = String(newString)
deallocate(self%item)
allocate(self%item(isize+1))
do i=1, isize + 1
self%item(i) = clist%item(i)
end do
else
allocate(self%item(1))
self%item(1) = String(newString)
end if
end subroutine
end module CharacterArrayClass