MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
listmodule Module Reference

Data Types

type  listtype
 A generic heterogeneous doubly-linked list. More...
 
interface  isEqualIface
 

Functions/Subroutines

class(iteratortype) function, allocatable iterator (this)
 
subroutine add (this, objptr)
 Append the given item to the list. More...
 
subroutine clear (this, destroy)
 Deallocate all items in list. More...
 
integer(i4b) function count (this)
 Return number of nodes in list. More...
 
logical function containsobject (this, obj, isEqual)
 Determine whether the list contains the given object. More...
 
subroutine deallocatebackward (this, fromNode)
 Deallocate fromNode and all previous nodes, and reassign firstNode. More...
 
integer(i4b) function getindex (this, obj)
 Get the index of the given item in the list. More...
 
class(*) function, pointer getnextitem (this)
 Get the next item in the list. More...
 
class(*) function, pointer getpreviousitem (this)
 Get the previous item in the list. More...
 
subroutine insertafter (this, objptr, indx)
 Insert the given item after the given index. More...
 
subroutine insertbefore (this, objptr, targetNode)
 Insert the given item before the given node. More...
 
subroutine next (this)
 Move the list's current node pointer and index one node forwards. More...
 
subroutine previous (this)
 Move the list's current node pointer and index one node backwards. More...
 
subroutine reset (this)
 Reset the list's current node pointer and index. More...
 
subroutine remove_node_by_index (this, i, destroyValue)
 Remove the node at the given index, optionally destroying its value. More...
 
subroutine remove_this_node (this, node, destroyValue)
 Remove the given node, optionally destroying its value. More...
 
class(*) function, pointer get_current_item (this)
 Get a pointer to the item at the current node. More...
 
class(*) function, pointer get_item_by_index (this, indx)
 Get a pointer to the item at the given index. More...
 
type(listnodetype) function, pointer get_node_by_index (this, indx)
 Get the node at the given index. More...
 

Function/Subroutine Documentation

◆ add()

subroutine listmodule::add ( class(listtype), intent(inout)  this,
class(*), intent(inout), pointer  objptr 
)
private

Definition at line 68 of file List.f90.

69  ! -- dummy variables
70  class(ListType), intent(inout) :: this
71  class(*), pointer, intent(inout) :: objptr
72  !
73  if (.not. associated(this%firstNode)) then
74  allocate (this%firstNode)
75  this%firstNode%Value => objptr
76  this%firstNode%prevNode => null()
77  this%lastNode => this%firstNode
78  else
79  allocate (this%lastNode%nextNode)
80  this%lastNode%nextNode%prevNode => this%lastNode
81  this%lastNode%nextNode%value => objptr
82  this%lastNode => this%lastNode%nextNode
83  end if
84  this%nodeCount = this%nodeCount + 1

◆ clear()

subroutine listmodule::clear ( class(listtype this,
logical, intent(in), optional  destroy 
)
private

Definition at line 88 of file List.f90.

89  ! -- dummy variables
90  class(ListType) :: this
91  logical, intent(in), optional :: destroy
92  ! -- local
93  logical :: destroyLocal
94  type(ListNodeType), pointer :: current => null()
95  type(ListNodeType), pointer :: next => null()
96  !
97  destroylocal = .false.
98  if (present(destroy)) then
99  destroylocal = destroy
100  end if
101  !
102  if (.not. associated(this%firstNode)) return
103  ! -- The last node will be deallocated in the loop below.
104  ! Just nullify the pointer to the last node to avoid
105  ! having a dangling pointer. Also nullify currentNode.
106  nullify (this%lastNode)
107  nullify (this%currentNode)
108  !
109  current => this%firstNode
110  do while (associated(current))
111  ! -- Assign a pointer to the next node in the list
112  next => current%nextNode
113  ! -- Deallocate the object stored in the current node
114  call current%DeallocValue(destroylocal)
115  ! -- Deallocate the current node
116  deallocate (current)
117  this%firstNode => next
118  this%nodeCount = this%nodeCount - 1
119  ! -- Advance to the next node
120  current => next
121  end do
122  !
123  call this%Reset()
124 

◆ containsobject()

logical function listmodule::containsobject ( class(listtype), intent(inout)  this,
class(*), pointer  obj,
procedure(isequaliface), intent(in), optional, pointer  isEqual 
)
private

Definition at line 135 of file List.f90.

136  class(ListType), intent(inout) :: this
137  class(*), pointer :: obj
138  procedure(isEqualIface), pointer, intent(in), optional :: isEqual
139  logical :: hasObj
140  ! local
141  type(ListNodeType), pointer :: current => null()
142 
143  hasobj = .false.
144  current => this%firstNode
145  do while (associated(current))
146  if (present(isequal)) then
147  if (isequal(current%Value, obj)) then
148  hasobj = .true.
149  return
150  end if
151  else
152  if (associated(current%Value, obj)) then
153  hasobj = .true.
154  return
155  end if
156  end if
157 
158  ! -- Advance to the next node
159  current => current%nextNode
160  end do
161 

◆ count()

integer(i4b) function listmodule::count ( class(listtype this)
private

Definition at line 128 of file List.f90.

129  integer(I4B) :: Count
130  class(ListType) :: this
131  count = this%nodeCount

◆ deallocatebackward()

subroutine listmodule::deallocatebackward ( class(listtype), intent(inout), target  this,
type(listnodetype), intent(inout), pointer  fromNode 
)
private

Definition at line 165 of file List.f90.

166  ! -- dummy
167  class(ListType), target, intent(inout) :: this
168  type(ListNodeType), pointer, intent(inout) :: fromNode
169  ! -- local
170  type(ListNodeType), pointer :: current => null()
171  type(ListNodeType), pointer :: prev => null()
172  !
173  if (associated(fromnode)) then
174  ! -- reassign firstNode
175  if (associated(fromnode%nextNode)) then
176  this%firstNode => fromnode%nextNode
177  else
178  this%firstNode => null()
179  end if
180  ! -- deallocate fromNode and all previous nodes
181  current => fromnode
182  do while (associated(current))
183  prev => current%prevNode
184  call current%DeallocValue(.true.)
185  deallocate (current)
186  this%nodeCount = this%nodeCount - 1
187  current => prev
188  end do
189  fromnode => null()
190  end if
191 

◆ get_current_item()

class(*) function, pointer listmodule::get_current_item ( class(listtype), intent(inout), target  this)
private

Definition at line 404 of file List.f90.

405  class(ListType), target, intent(inout) :: this
406  ! result
407  class(*), pointer :: resultobj
408  !
409  resultobj => null()
410  if (associated(this%currentNode)) then
411  resultobj => this%currentNode%Value
412  end if
Here is the caller graph for this function:

◆ get_item_by_index()

class(*) function, pointer listmodule::get_item_by_index ( class(listtype), intent(inout)  this,
integer(i4b), intent(in)  indx 
)
private

Definition at line 416 of file List.f90.

417  ! -- dummy
418  class(ListType), intent(inout) :: this
419  integer(I4B), intent(in) :: indx
420  ! result
421  class(*), pointer :: resultobj
422  ! -- local
423  integer(I4B) :: i
424  !
425  ! -- Initialize
426  resultobj => null()
427  !
428  ! -- Ensure that this%currentNode is associated
429  if (.not. associated(this%currentNode)) then
430  this%currentNodeIndex = 0
431  end if
432  if (this%currentNodeIndex == 0) then
433  if (associated(this%firstNode)) then
434  this%currentNode => this%firstNode
435  this%currentNodeIndex = 1
436  end if
437  end if
438  !
439  ! -- Check indx position relative to current node index
440  i = 0
441  if (indx < this%currentNodeIndex) then
442  ! Start at beginning of list
443  call this%Reset()
444  if (associated(this%firstNode)) then
445  this%currentNode => this%firstNode
446  this%currentNodeIndex = 1
447  i = 1
448  end if
449  else
450  i = this%currentNodeIndex
451  end if
452  if (i == 0) return
453  !
454  ! -- If current node is requested node,
455  ! assign pointer and return
456  if (i == indx) then
457  resultobj => this%currentNode%Value
458  return
459  end if
460  !
461  ! -- Iterate from current node to requested node
462  do while (associated(this%currentNode%nextNode))
463  this%currentNode => this%currentNode%nextNode
464  this%currentNodeIndex = this%currentNodeIndex + 1
465  if (this%currentNodeIndex == indx) then
466  resultobj => this%currentNode%Value
467  return
468  end if
469  end do
Here is the caller graph for this function:

◆ get_node_by_index()

type(listnodetype) function, pointer listmodule::get_node_by_index ( class(listtype), intent(inout)  this,
integer(i4b), intent(in)  indx 
)
private

Definition at line 473 of file List.f90.

474  ! -- dummy
475  class(ListType), intent(inout) :: this
476  integer(I4B), intent(in) :: indx
477  ! result
478  type(ListNodeType), pointer :: resultnode
479  ! -- local
480  integer(I4B) :: i
481  !
482  ! -- Initialize
483  resultnode => null()
484  !
485  ! -- Ensure that this%currentNode is associated
486  if (this%currentNodeIndex == 0) then
487  if (associated(this%firstNode)) then
488  this%currentNode => this%firstNode
489  this%currentNodeIndex = 1
490  end if
491  end if
492  !
493  ! -- Check indx position relative to current node index
494  i = 0
495  if (indx < this%currentNodeIndex) then
496  ! Start at beginning of list
497  call this%Reset()
498  if (associated(this%firstNode)) then
499  this%currentNode => this%firstNode
500  this%currentNodeIndex = 1
501  i = 1
502  end if
503  else
504  i = this%currentNodeIndex
505  end if
506  if (i == 0) return
507  !
508  ! -- If current node is requested node,
509  ! assign pointer and return
510  if (i == indx) then
511  resultnode => this%currentNode
512  return
513  end if
514  !
515  ! -- Iterate from current node to requested node
516  do while (associated(this%currentNode%nextNode))
517  this%currentNode => this%currentNode%nextNode
518  this%currentNodeIndex = this%currentNodeIndex + 1
519  if (this%currentNodeIndex == indx) then
520  resultnode => this%currentNode
521  return
522  end if
523  end do

◆ getindex()

integer(i4b) function listmodule::getindex ( class(listtype), intent(inout), target  this,
class(*), pointer  obj 
)
private

Definition at line 195 of file List.f90.

196  class(ListType), target, intent(inout) :: this
197  class(*), pointer :: obj
198  integer(I4B) :: idx
199  ! local
200  integer(I4B) :: i
201  class(*), pointer :: obj_in_list
202 
203  idx = -1
204  do i = 1, this%Count()
205  obj_in_list => this%GetItem(i)
206  if (associated(obj, obj_in_list)) then
207  idx = i
208  exit
209  end if
210  end do
211 

◆ getnextitem()

class(*) function, pointer listmodule::getnextitem ( class(listtype), intent(inout), target  this)
private

Definition at line 215 of file List.f90.

216  class(ListType), target, intent(inout) :: this
217  class(*), pointer :: resultobj
218  call this%Next()
219  resultobj => this%get_current_item()

◆ getpreviousitem()

class(*) function, pointer listmodule::getpreviousitem ( class(listtype), intent(inout), target  this)
private

Definition at line 223 of file List.f90.

224  class(ListType), target, intent(inout) :: this
225  class(*), pointer :: resultobj
226  call this%Previous()
227  resultobj => this%get_current_item()

◆ insertafter()

subroutine listmodule::insertafter ( class(listtype), intent(inout)  this,
class(*), intent(inout), pointer  objptr,
integer(i4b), intent(in)  indx 
)
private

Definition at line 231 of file List.f90.

232  ! -- dummy
233  class(ListType), intent(inout) :: this
234  class(*), pointer, intent(inout) :: objptr
235  integer(I4B), intent(in) :: indx
236  ! -- local
237  integer(I4B) :: numnodes
238  type(ListNodeType), pointer :: precedingNode => null()
239  type(ListNodeType), pointer :: followingNode => null()
240  type(ListNodeType), pointer :: newNode => null()
241  !
242  numnodes = this%Count()
243  if (indx >= numnodes) then
244  call this%Add(objptr)
245  else
246  precedingnode => this%get_node_by_index(indx)
247  if (associated(precedingnode%nextNode)) then
248  followingnode => precedingnode%nextNode
249  allocate (newnode)
250  newnode%Value => objptr
251  newnode%nextNode => followingnode
252  newnode%prevNode => precedingnode
253  precedingnode%nextNode => newnode
254  followingnode%prevNode => newnode
255  this%nodeCount = this%nodeCount + 1
256  else
257  call pstop(1, 'Programming error in ListType%insert_after')
258  end if
259  end if
260 
Here is the call graph for this function:

◆ insertbefore()

subroutine listmodule::insertbefore ( class(listtype), intent(inout)  this,
class(*), intent(inout), pointer  objptr,
type(listnodetype), intent(inout), pointer  targetNode 
)
private

Definition at line 264 of file List.f90.

265  ! -- dummy
266  class(ListType), intent(inout) :: this
267  class(*), pointer, intent(inout) :: objptr
268  type(ListNodeType), pointer, intent(inout) :: targetNode
269  ! -- local
270  type(ListNodeType), pointer :: newNode => null()
271  !
272  if (.not. associated(targetnode)) &
273  call pstop(1, 'Programming error in ListType%InsertBefore')
274  !
275  ! Allocate a new list node and point its Value member to the object
276  allocate (newnode)
277  newnode%Value => objptr
278  !
279  ! Do the insertion
280  newnode%nextNode => targetnode
281  if (associated(targetnode%prevNode)) then
282  ! Insert between two nodes
283  targetnode%prevNode%nextNode => newnode
284  newnode%prevNode => targetnode%prevNode
285  else
286  ! Insert before first node
287  this%firstNode => newnode
288  newnode%prevNode => null()
289  end if
290  targetnode%prevNode => newnode
291  this%nodeCount = this%nodeCount + 1
292 
Here is the call graph for this function:

◆ iterator()

class(iteratortype) function, allocatable listmodule::iterator ( class(listtype this)
private

Definition at line 60 of file List.f90.

61  class(ListType) :: this
62  class(IteratorType), allocatable :: itr
63 
64  itr = listiteratortype(this%firstNode)

◆ next()

subroutine listmodule::next ( class(listtype), intent(inout), target  this)
private

Definition at line 296 of file List.f90.

297  class(ListType), target, intent(inout) :: this
298 
299  if (this%currentNodeIndex == 0) then
300  if (associated(this%firstNode)) then
301  this%currentNode => this%firstNode
302  this%currentNodeIndex = 1
303  else
304  this%currentNode => null()
305  this%currentNodeIndex = 0
306  end if
307  else
308  if (associated(this%currentNode%nextNode)) then
309  this%currentNode => this%currentNode%nextNode
310  this%currentNodeIndex = this%currentNodeIndex + 1
311  else
312  this%currentNode => null()
313  this%currentNodeIndex = 0
314  end if
315  end if

◆ previous()

subroutine listmodule::previous ( class(listtype), intent(inout), target  this)
private

Definition at line 319 of file List.f90.

320  class(ListType), target, intent(inout) :: this
321  if (this%currentNodeIndex <= 1) then
322  call this%Reset()
323  else
324  this%currentNode => this%currentNode%prevNode
325  this%currentNodeIndex = this%currentNodeIndex - 1
326  end if

◆ remove_node_by_index()

subroutine listmodule::remove_node_by_index ( class(listtype), intent(inout)  this,
integer(i4b), intent(in)  i,
logical, intent(in)  destroyValue 
)
private

Definition at line 337 of file List.f90.

338  ! -- dummy
339  class(ListType), intent(inout) :: this
340  integer(I4B), intent(in) :: i
341  logical, intent(in) :: destroyValue
342  ! -- local
343  type(ListNodeType), pointer :: node
344  !
345  node => null()
346  node => this%get_node_by_index(i)
347  if (associated(node)) then
348  call this%remove_this_node(node, destroyvalue)
349  end if
350 
Here is the caller graph for this function:

◆ remove_this_node()

subroutine listmodule::remove_this_node ( class(listtype), intent(inout)  this,
type(listnodetype), intent(inout), pointer  node,
logical, intent(in)  destroyValue 
)
private

Definition at line 354 of file List.f90.

355  ! -- dummy
356  class(ListType), intent(inout) :: this
357  type(ListNodeType), pointer, intent(inout) :: node
358  logical, intent(in) :: destroyValue
359  ! -- local
360  !
361  logical :: first, last
362  !
363  first = .false.
364  last = .false.
365  if (associated(node)) then
366  if (associated(node%prevNode)) then
367  if (associated(node%nextNode)) then
368  node%nextNode%prevNode => node%prevNode
369  else
370  node%prevNode%nextNode => null()
371  this%lastNode => node%prevNode
372  end if
373  else
374  first = .true.
375  end if
376  if (associated(node%nextNode)) then
377  if (associated(node%prevNode)) then
378  node%prevNode%nextNode => node%nextNode
379  else
380  node%nextNode%prevNode => null()
381  this%firstNode => node%nextNode
382  end if
383  else
384  last = .true.
385  end if
386  if (destroyvalue) then
387  call node%DeallocValue(destroyvalue)
388  end if
389  deallocate (node)
390  this%nodeCount = this%nodeCount - 1
391  if (first .and. last) then
392  this%firstNode => null()
393  this%lastNode => null()
394  this%currentNode => null()
395  end if
396  call this%Reset()
397  end if
398 
Here is the caller graph for this function:

◆ reset()

subroutine listmodule::reset ( class(listtype), intent(inout), target  this)
private

Definition at line 330 of file List.f90.

331  class(ListType), target, intent(inout) :: this
332  this%currentNode => null()
333  this%currentNodeIndex = 0