-
Notifications
You must be signed in to change notification settings - Fork 0
/
NeuralTract.f90
154 lines (119 loc) · 5.33 KB
/
NeuralTract.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
! '''
! 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 NeuralTractClass
! '''
! Class that implements a a neural tract, composed by the descending
! commands from the motor cortex.
! '''
use NeuralTractUnitClass
use ConfigurationClass
implicit none
private
integer, parameter :: wp = kind(1.0d0)
public :: NeuralTract
type NeuralTract
type(NeuralTractUnit), dimension(:), allocatable :: unit
type(Configuration), pointer :: conf
character(len = 6) :: poolKind, pool
integer :: Number
real(wp) , dimension(:,:), allocatable :: poolTerminalSpikes
contains
procedure :: atualizePool
procedure :: listSpikes
procedure :: reset
end type NeuralTract
interface NeuralTract
module procedure init_NeuralTract
end interface
contains
type(NeuralTract) function init_NeuralTract(conf, pool)
! '''
! Constructor
! - Inputs:
! + **conf**: Configuration object with the simulation parameters.
! + **pool**: string with the name of the Neural tract.
! '''
character(len = 6), intent(in) :: pool
class(Configuration), intent(in), target :: conf
character(len=80) :: paramTag, paramChar
real(wp) :: paramReal
integer :: i
init_NeuralTract%conf => conf
! ## Indicates that is a neural tract.
init_NeuralTract%poolKind = 'NT'
! ## String with the name of the Neural tract.
init_NeuralTract%pool = pool
! ## The number of neural tract units.
paramTag = 'Number_' // pool
paramChar = init_NeuralTract%conf%parameterSet(paramTag, pool, 0)
read(paramChar, *)paramReal
init_NeuralTract%Number = int(paramReal)
! ## List of NeuralTRactUnit objects.
allocate(init_NeuralTract%unit(init_NeuralTract%Number))
do i = 1, init_NeuralTract%Number
init_NeuralTract%unit(i) = NeuralTractUnit(pool, i)
end do
print '(A)', 'Descending Command ' // pool // ' built'
end function init_NeuralTract
subroutine atualizePool(self, t, FR, GammaOrder)
! '''
! Update all neural tract units from the neural tract.
! - Inputs:
! + **t**: current instant, in ms.
! + **FR**: firing rate, in Hz
! + **GammaOrder** : order of the Gamma distribution, integer
! '''
class(NeuralTract), intent(inout) :: self
real(wp), intent(in) :: t, FR
integer, intent(in) :: GammaOrder
integer :: i
real(wp) :: FiringRate
FiringRate = FR*self%conf%timeStep_ms/1000.0
do i = 1, self%Number
call self%unit(i)%atualizeNeuralTractUnit(t, FiringRate , GammaOrder)
end do
end subroutine
subroutine listSpikes(self)
! '''
! List the spikes that occurred in neural tract units.
! '''
class(NeuralTract), intent(inout) :: self
integer :: i
integer :: numberOfSpikes, initInd, endInd
integer, dimension(self%Number) :: numberOfNewSpikes
do i = 1, self%Number
numberOfNewSpikes(i) = size(self%unit(i)%spikesGenerator%points)
end do
numberOfSpikes = sum(numberOfNewSpikes)
allocate(self%poolTerminalSpikes(numberOfSpikes,2))
initInd = 1
do i = 1, self%Number
endInd = initInd + size(self%unit(i)%spikesGenerator%points) - 1
self%poolTerminalSpikes(initInd:endInd,1) = self%unit(i)%spikesGenerator%points
self%poolTerminalSpikes(initInd:endInd,2) = i
initInd = endInd+1
end do
end subroutine
subroutine reset(self)
class(NeuralTract), intent(inout) :: self
integer :: i
do i = 1, self%Number
call self%unit(i)%reset()
end do
if (allocated(self%poolTerminalSpikes)) deallocate(self%poolTerminalSpikes)
print *, 'Neural tract reseted'
end subroutine
end module NeuralTractClass