ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/forceGlobals.F90 (file contents):
Revision 306 by chuckv, Mon Mar 10 19:26:45 2003 UTC vs.
Revision 319 by gezelter, Wed Mar 12 14:29:15 2003 UTC

# Line 1 | Line 1
1   module forceGlobals
2 <
3 <
4 <
5 < !! Number of lj_atypes in lj_atype_list
6 <  integer, save :: n_atypes = 0
7 <
8 < !! Global list of lj atypes in simulation
9 <  type (atype), pointer :: ListHead => null()
10 <  type (atype), pointer :: ListTail => null()
11 <
12 <
13 <
14 <
15 <  logical, save :: firstTime = .True.
16 <
17 < !! Atype identity pointer lists
2 >  
3 >  use definitions
4 >  use simulation
5 >  use atype_typedefs
6 >  use vector_class
7   #ifdef IS_MPI
8 < !! Row lj_atype pointer list
20 <  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
21 < !! Column lj_atype pointer list
22 <  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
23 < #else
24 <  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
8 >  use mpiSimulation
9   #endif
10 +    
11 +  logical, save :: atype_vector_initialized = .false.
12 +  logical, save :: ff_initialized = .false.
13  
14 <
28 < !! Logical has lj force field module been initialized?
29 <  logical, save :: isFFinit = .false.
30 <
31 < !! Use periodic boundry conditions
32 <  logical :: wrap = .false.
33 <
34 < !! Potential energy global module variables
14 >  
15   #ifdef IS_MPI
16 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
17 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
18 <
19 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
20 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
21 <
22 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
23 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
24 <
25 <  real(kind = dp), dimension(9,getNrow(plan_row)) :: ARow = 0.0_dp
26 <  real(kind = dp), dimension(9,getNcol(plan_col)) :: ACol = 0.0_dp  
27 <
28 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
29 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
30 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp1 = 0.0_dp
31 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp1 = 0.0_dp
32 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp2 = 0.0_dp
33 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp2 = 0.0_dp
34 <  real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
35 <  real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
56 <
57 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
58 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
59 <
60 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: rflRow = 0.0_dp
61 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: rflCol = 0.0_dp
62 <  real(kind = dp), dimension(3,getNlocal()) :: rflTemp = 0.0_dp
63 <
64 <  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
65 <  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
66 <
67 <  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
16 >  real( kind = dp ), allocatable, dimension(:,:) :: q_Row
17 >  real( kind = dp ), allocatable, dimension(:,:) :: q_Col
18 >  real( kind = dp ), allocatable, dimension(:,:) :: u_l_Row
19 >  real( kind = dp ), allocatable, dimension(:,:) :: u_l_Col
20 >  real( kind = dp ), allocatable, dimension(:,:) :: A_Row
21 >  real( kind = dp ), allocatable, dimension(:,:) :: A_Col
22 >  
23 >  real( kind = dp ), allocatable, dimension(:) :: pot_Row
24 >  real( kind = dp ), allocatable, dimension(:) :: pot_Col
25 >  real( kind = dp ), allocatable, dimension(:) :: pot_Temp
26 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Row
27 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Col
28 >  real( kind = dp ), allocatable, dimension(:,:) :: f_Temp
29 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Row
30 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Col
31 >  real( kind = dp ), allocatable, dimension(:,:) :: t_Temp
32 >  integer, allocatable, dimension(:) :: atid_Row
33 >  integer, allocatable, dimension(:) :: atid_Col
34 > #else
35 >  integer, allocatable, dimension(:) :: atid
36   #endif
37 <  real(kind = dp) :: pe = 0.0_dp
38 <  real(kind = dp), dimension(3,natoms) :: fTemp = 0.0_dp
39 <  real(kind = dp), dimension(3,natoms) :: tTemp = 0.0_dp
40 <  real(kind = dp), dimension(3,natoms) :: rflTemp = 0.0_dp
41 <  real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
74 <
75 <  logical :: do_preForce  = .false.
76 <  logical :: do_postForce = .false.
77 <
78 <
79 <
80 < !! Public methods and data
37 >  
38 >  real(kind = dp) :: pot = 0.0_dp
39 >  real(kind = dp), dimension(9) :: tau_Temp = 0.0_dp
40 >  real(kind = dp) :: virial_Temp = 0.0_dp
41 >  
42    public :: new_atype
82  public :: do_forceLoop
43    public :: init_FF
44  
45 + contains
46    
47 +  subroutine new_atype(c_ident, is_LJ, is_Sticky, is_DP, is_GB, &
48 +       lj_epsilon, lj_sigma, &
49 +       dipole_moment, &
50 +       sticky_w0, sticky_v0, &
51 +       GB_sigma, GB_l2b_ratio, GB_eps, GB_eps_ratio, GB_mu, GB_nu, &
52 +       status)
53 +    
54 +    real( kind = dp ), intent(in) :: lj_epsilon
55 +    real( kind = dp ), intent(in) :: lj_sigma
56 +    real( kind = dp ), intent(in) :: sticky_w0
57 +    real( kind = dp ), intent(in) :: sticky_v0
58 +    real( kind = dp ), intent(in) :: dipole_moment
59 +    real( kind = dp ), intent(in) :: GB_sigma, GB_l2b_ratio, GB_eps
60 +    real( kind = dp ), intent(in) :: GB_eps_ratio, GB_mu, GB_nu
61  
62 <
88 < contains
89 <
90 < !! Adds a new lj_atype to the list.
91 <  subroutine new_atype(ident,mass,epsilon,sigma, &
92 <       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
93 <    real( kind = dp ), intent(in) :: mass
94 <    real( kind = dp ), intent(in) :: epsilon
95 <    real( kind = dp ), intent(in) :: sigma
96 <    real( kind = dp ), intent(in) :: w0
97 <    real( kind = dp ), intent(in) :: v0
98 <    real( kind = dp ), intent(in) :: dipoleMoment
99 <
100 <    integer, intent(in) :: ident
62 >    integer, intent(in)  :: c_ident
63      integer, intent(out) :: status
64 <    integer, intent(in) :: is_Sticky
65 <    integer, intent(in) :: is_DP
66 <    integer, intent(in) :: is_GB
67 <    integer, intent(in) :: is_LJ
64 >    integer, intent(in)  :: is_Sticky
65 >    integer, intent(in)  :: is_DP
66 >    integer, intent(in)  :: is_GB
67 >    integer, intent(in)  :: is_LJ
68 >    integer :: me
69 >    logical :: l_is_LJ, l_is_DP, l_is_Sticky, l_is_GB
70  
107
108    type (atype), pointer :: the_new_atype
109    integer :: alloc_error
110    integer :: atype_counter = 0
111    integer :: alloc_size
112    integer :: err_stat
71      status = 0
72  
73 +    if (.not.atype_vector_initialized) then
74 +       !! There are 16 properties to worry about for now.  
75 +       !! Fix this if needed for more atomic properties
76 +       atypes = initialize(16)
77 +       if (.not.associated(atypes)) then
78 +          status = -1
79 +          return
80 +       endif
81 +    endif
82  
83 +    me = addElement(atypes)
84  
85 < ! allocate a new atype    
118 <    allocate(the_new_atype,stat=alloc_error)
119 <    if (alloc_error /= 0 ) then
120 <       status = -1
121 <       return
122 <    end if
85 >    call setElementProperty(atypes, me, "c_ident", c_ident)
86  
87 < ! assign our new atype information
88 <    the_new_atype%mass        = mass
89 <    the_new_atype%epsilon     = epsilon
90 <    the_new_atype%sigma       = sigma
128 <    the_new_atype%sigma2      = sigma * sigma
129 <    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
130 <         * the_new_atype%sigma2
131 <    the_new_atype%w0       = w0
132 <    the_new_atype%v0       = v0
133 <    the_new_atype%dipoleMoment       = dipoleMoment
134 <
135 <    
136 < ! assume that this atype will be successfully added
137 <    the_new_atype%atype_ident = ident
138 <    the_new_atype%atype_number = n_lj_atypes + 1
139 <    
140 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
141 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
142 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
143 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
87 >    l_is_LJ = (is_LJ .ne. 0)
88 >    l_is_DP = (is_DP .ne. 0)
89 >    l_is_Sticky = (is_Sticky .ne. 0)
90 >    l_is_GB = (is_GB .ne. 0)
91  
92 <    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
93 <    if (err_stat /= 0 ) then
94 <       status = -1
95 <       return
92 >    call setElementProperty(atypes, me, "is_LJ", l_is_LJ)
93 >    call setElementProperty(atypes, me, "is_DP", l_is_DP)
94 >    call setElementProperty(atypes, me, "is_Sticky", l_is_Sticky)
95 >    call setElementProperty(atypes, me, "is_GB", l_is_GB)
96 >
97 >    if (l_is_LJ) then
98 >       call setElementProperty(atypes, me, "lj_sigma", lj_sigma)
99 >       call setElementProperty(atypes, me, "lj_epsilon", lj_epsilon)
100      endif
101 +    if (l_is_DP) then
102 +       call setElementProperty(atypes, me, "dipole_moment", dipole_moment)
103 +    endif
104 +    if (l_is_Sticky) then
105 +       call setElementProperty(atypes, me, "sticky_w0", sticky_w0)
106 +       call setElementProperty(atypes, me, "sticky_v0", sticky_v0)
107 +    endif
108 +    if (l_is_GB) then
109 +       call setElementProperty(atypes, me, "GB_sigma", GB_sigma)
110 +       call setElementProperty(atypes, me, "GB_l2b_ratio", GB_l2b_ratio)
111 +       call setElementProperty(atypes, me, "GB_eps", GB_eps)
112 +       call setElementProperty(atypes, me, "GB_eps_ratio", GB_eps_ratio)
113 +       call setElementProperty(atypes, me, "GB_mu", GB_mu)
114 +       call setElementProperty(atypes, me, "GB_nu", GB_nu)
115 +    endif
116  
151    n_atypes = n_atypes + 1
152
153
117    end subroutine new_atype
118  
119 <
120 <  subroutine init_FF(nComponents,ident, nExcludes,excludesLocal,status)
121 < !! Number of components in ident array
119 >  
120 >  subroutine init_FF(nComponents, c_idents, nExcludes, excludesLocal, status)
121 >    !! Number of components in c_idents array
122      integer, intent(inout) :: nComponents
123 < !! Array of identities nComponents long corresponding to
124 < !! ljatype ident.
125 <    integer, dimension(nComponents),intent(inout) :: ident
123 >    !! Array of identities nComponents long corresponding to
124 >    !! ljatype ident.
125 >    integer, dimension(nComponents),intent(inout) :: c_idents
126      integer :: nExcludes
127 <    integer, dimension(n),intent(inout) :: excludesLocal
128 < !!  Result status, success = 0, error = -1
129 <    integer, intent(out) :: Status
130 <
168 <    integer :: alloc_stat
169 <
170 <    integer :: thisStat
171 <    integer :: i
172 <
127 >    integer, dimension(nExcludes),intent(inout) :: excludesLocal
128 >    !!  Result status, success = 0, error = -1
129 >    integer, intent(out) :: status    
130 >    integer :: i, me, thisStat
131      integer :: myNode
132 +
133   #ifdef IS_MPI
134 <    integer, allocatable, dimension(:) :: identRow
135 <    integer, allocatable, dimension(:) :: identCol
134 >    integer, allocatable, dimension(:) :: c_idents_Row
135 >    integer, allocatable, dimension(:) :: c_idents_Col
136      integer :: nrow
137      integer :: ncol
138   #endif
139 +
140      status = 0
181  
141  
183    
142  
143 < !! if were're not in MPI, we just update ljatypePtrList
144 < #ifndef IS_MPI
187 <    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
188 <    if ( thisStat /= 0 ) then
189 <       status = -1
190 <       return
191 <    endif
192 <
193 <    
194 < ! if were're in MPI, we also have to worry about row and col lists    
195 < #else
196 <  
197 < ! We can only set up forces if mpiSimulation has been setup.
143 > #ifdef IS_MPI
144 >    ! We can only set up forces if mpiSimulation has been setup.
145      if (.not. isMPISimSet()) then
146         write(default_error,*) "MPI is not set"
147         status = -1
# Line 203 | Line 150 | contains
150      nrow = getNrow(plan_row)
151      ncol = getNcol(plan_col)
152      mynode = getMyNode()
153 < !! Allocate temperary arrays to hold gather information
154 <    allocate(identRow(nrow),stat=alloc_stat)
153 >    
154 >    allocate(c_idents_Row(nrow),stat=alloc_stat)
155      if (alloc_stat /= 0 ) then
156         status = -1
157         return
158      endif
159  
160 <    allocate(identCol(ncol),stat=alloc_stat)
160 >    allocate(c_idents_Col(ncol),stat=alloc_stat)
161      if (alloc_stat /= 0 ) then
162         status = -1
163         return
164      endif
165  
166 < !! Gather idents into row and column idents
167 <
168 <    call gather(ident,identRow,plan_row)
169 <    call gather(ident,identCol,plan_col)
170 <    
224 <  
225 < !! Create row and col pointer lists
226 <  
227 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
228 <    if (thisStat /= 0 ) then
166 >    call gather(c_idents, c_idents_Row, plan_row)
167 >    call gather(c_idents, c_idents_Col, plan_col)
168 >
169 >    allocate(atid_Row(nrow),stat=alloc_stat)
170 >    if (alloc_stat /= 0 ) then
171         status = -1
172         return
173      endif
174 <  
175 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
176 <    if (thisStat /= 0 ) then
174 >
175 >    allocate(atid_Col(ncol),stat=alloc_stat)
176 >    if (alloc_stat /= 0 ) then
177         status = -1
178         return
179      endif
180  
181 < !! free temporary ident arrays
181 >    do i = 1, nrow
182 >       me = getFirstMatchingElement(atypes, "c_ident", c_idents_Row(i))
183 >       atid_Row(i) = me
184 >    enddo
185 >
186 >    do i = 1, ncol
187 >       me = getFirstMatchingElement(atypes, "c_ident", c_idents_Col(i))
188 >       atid_Col(i) = me
189 >    enddo
190 >
191 >    !! free temporary ident arrays
192      if (allocated(identCol)) then
193         deallocate(identCol)
194      end if
195      if (allocated(identCol)) then
196         deallocate(identRow)
197      endif
198 +    
199 + #else
200 +    do i = 1, nComponents
201  
202 +       me = getFirstMatchingElement(atypes, "c_ident", c_idents(i))
203 +       atid(i) = me
204 +
205 +    enddo
206   #endif
207 <    
207 >
208      call initForce_Modules(thisStat)
209      if (thisStat /= 0) then
210         status = -1
211         return
212      endif
213 <
214 < !! Create neighbor lists
213 >    
214 >    !! Create neighbor lists
215      call expandList(thisStat)
216      if (thisStat /= 0) then
217         status = -1
218         return
219      endif
220 +    
221 +    call setupGlobals(thisStat)
222 +    if (thisStat /= 0) then
223 +       status = -1
224 +       return
225 +    endif
226 +    
227 +    ff_initialized = .true.
228 +    
229 +    
230 +  end subroutine init_FF
231 +  
232 +  subroutine setupGlobals(thisStat)
233 +    integer, intent(out) :: thisStat
234 +    integer :: nrow
235 +    integer :: ncol
236 +    integer :: nlocal
237 +    integer :: ndim = 3
238 +    integer :: alloc_stat
239  
240 <    isFFinit = .true.
240 >    thisStat = 0
241  
242 + #ifdef IS_MPI
243 +    nrow = getNrow(plan_row)
244 +    ncol = getNcol(plan_col)
245 + #endif
246 +    nlocal = getNlocal()
247  
248 <  end subroutine init_FF
248 >    call freeGlobals()
249  
250 +    allocate(q_Row(ndim,nrow),stat=alloc_stat)
251 +    if (alloc_stat /= 0 ) then
252 +       thisStat = 0
253 +       return
254 +    endif
255 +    
256 +    
257 +    allocate(q_Col(ndim,ncol),stat=alloc_stat)
258 +    if (alloc_stat /= 0 ) then
259 +       thisStat = 0
260 +       return
261 +    endif
262 +    
263 +    
264 +    allocate(u_l_Row(ndim,nrow),stat=alloc_stat)
265 +    if (alloc_stat /= 0 ) then
266 +       thisStat = 0
267 +       return
268 +    endif
269 +    
270 +    allocate(u_l_Col(ndim,ncol),stat=alloc_stat)
271 +    if (alloc_stat /= 0 ) then
272 +       thisStat = 0
273 +       return
274 +    endif
275 +    
276  
277 +    allocate(A_row(9,nrow),stat=alloc_stat)
278 +    if (alloc_stat /= 0 ) then
279 +       thisStat = 0
280 +       return
281 +    endif
282 +    
283 +    
284 +    allocate(A_Col(9,ncol),stat=alloc_stat)
285 +    if (alloc_stat /= 0 ) then
286 +       thisStat = 0
287 +       return
288 +    endif
289 +    
290  
291 +    allocate(pot_row(nrow),stat=alloc_stat)
292 +    if (alloc_stat /= 0 ) then
293 +       thisStat = 0
294 +       return
295 +    endif
296 +    
297 +    allocate(pot_Col(ncol),stat=alloc_stat)
298 +    if (alloc_stat /= 0 ) then
299 +       thisStat = 0
300 +       return
301 +    endif
302  
303 <  subroutine initForce_Modules(thisStat)
304 <    integer, intent(out) :: thisStat
305 <    integer :: my_status
303 >    allocate(pot_Temp(nlocal),stat=alloc_stat)
304 >    if (alloc_stat /= 0 ) then
305 >       thisStat = 0
306 >       return
307 >    endif
308      
309 <    thisStat = 0
310 <    call init_lj_FF(ListHead,my_status)
311 <    if (my_status /= 0) then
277 <       thisStat = -1
309 >    allocate(f_Row(ndim,nrow),stat=alloc_stat)
310 >    if (alloc_stat /= 0 ) then
311 >       thisStat = 0
312         return
313 +    endif
314 +    
315 +    allocate(f_Col(ndim,ncol),stat=alloc_stat)
316 +    if (alloc_stat /= 0 ) then
317 +       thisStat = 0
318 +       return
319 +    endif
320 +    
321 +    allocate(f_Temp(ndim,nlocal),stat=alloc_stat)
322 +    if (alloc_stat /= 0 ) then
323 +       thisStat = 0
324 +       return
325 +    endif
326 +    
327 +    allocate(t_Row(ndim,nrow),stat=alloc_stat)
328 +    if (alloc_stat /= 0 ) then
329 +       thisStat = 0
330 +       return
331 +    endif
332 +    
333 +    allocate(t_Col(ndim,ncol),stat=alloc_stat)
334 +    if (alloc_stat /= 0 ) then
335 +       thisStat = 0
336 +       return
337 +    endif
338 +
339 +    allocate(t_temp(ndim,nlocal),stat=alloc_stat)
340 +    if (alloc_stat /= 0 ) then
341 +       thisStat = 0
342 +       return
343 +    endif
344 +
345 +    allocate(atid_Row(nrow),stat=alloc_stat)
346 +    if (alloc_stat /= 0 ) then
347 +       thisStat = 0
348 +       return
349 +    endif
350 +
351 +    allocate(atid_Col(ncol),stat=alloc_stat)
352 +    if (alloc_stat /= 0 ) then
353 +       thisStat = 0
354 +       return
355 +    endif
356 +
357 + #else
358 +
359 +    allocate(atid(nlocal),stat=alloc_stat)
360 +    if (alloc_stat /= 0 ) then
361 +       thisStat = 0
362 +       return
363      end if
364 + #endif
365  
366 <  end subroutine initForce_Modules
366 >  end subroutine setupGlobals
367 >  
368 >  subroutine freeGlobals()
369  
370 + !We free in the opposite order in which we allocate in.
371 + #ifdef IS_MPI
372  
373 +    if (allocated(atid_Col))   deallocate(atid_Col)
374 +    if (allocated(atid_Row))   deallocate(atid_Row)
375 +    if (allocated(t_Temp))     deallocate(t_Temp)
376 +    if (allocated(t_Col))      deallocate(t_Col)
377 +    if (allocated(t_Row))      deallocate(t_Row)
378 +    if (allocated(f_Temp))     deallocate(f_Temp)
379 +    if (allocated(f_Col))      deallocate(f_Col)
380 +    if (allocated(f_Row))      deallocate(f_Row)
381 +    if (allocated(pot_Temp))   deallocate(pot_Temp)
382 +    if (allocated(pot_Col))    deallocate(pot_Col)
383 +    if (allocated(pot_Row))    deallocate(pot_Row)
384 +    if (allocated(A_Col))      deallocate(A_Col)
385 +    if (allocated(A_Row))      deallocate(A_Row)
386 +    if (allocated(u_l_Col))    deallocate(u_l_Col)
387 +    if (allocated(u_l_Row))    deallocate(u_l_Row)
388 +    if (allocated(q_Col))      deallocate(q_Col)
389 +    if (allocated(q_Row))      deallocate(q_Row)
390  
391 + #else
392  
393 +    if (allocated(atid))       deallocate(atid)
394  
395 + #endif
396  
397  
398 +  end subroutine freeGlobals
399 +
400 +
401 +
402 +
403 +  
404 +  subroutine initForce_Modules(thisStat)
405 +    integer, intent(out) :: thisStat
406 +    integer :: my_status
407 +    
408 +    thisStat = 0
409 +    call init_lj_FF(my_status)
410 +    if (my_status /= 0) then
411 +       thisStat = -1
412 +       return
413 +    end if
414 +    
415 +  end subroutine initForce_Modules
416 +  
417   end module forceGlobals

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines