GRIDMAN
grid managment library
indlist.f
Go to the documentation of this file.
1 C> @file indlist.f
2 C> Methods of data-type GRIDMAN_INDLIS, see gridman.f
3 C>
4 C> List of elements with variable number of indices for each element
5 
6 ! Copyright (c) 2017 Forschungszentrum Juelich GmbH
7 ! Vladislav Kotov
8 !
9 ! This file is part of GRIDMAN.
10 !
11 ! GRIDMAN is free software: you can redistribute it and/or modify
12 ! it under the terms of the GNU General Public License as published by
13 ! the Free Software Foundation, either version 3 of the License, or
14 ! (at your option) any later version.
15 !
16 ! GRIDMAN is distributed in the hope that it will be useful,
17 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
18 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 ! GNU General Public License for more details.
20 !
21 ! You should have received a copy of the GNU General Public License
22 
23 C
24 C GRIDMAN, grid managment library. Author: Vladislav Kotov, v.kotov@fz-juelich.de
25 C
26 C *****************************************************************************************
27 C> Allocate list of elements
28 C>
29 C> WARNING: if INDLIST elready exists it will be re-allocated
30 C *****************************************************************************************
31  SUBROUTINE gridman_indlist_allocate(INDLIST,N,L,IERR)
33  u gridman_dbg,gridman_unit
34  IMPLICIT NONE
35 C> Resulting list of elements object
36  TYPE(gridman_indlist) :: INDLIST
37 C> Number of elements
38  INTEGER(GRIDMAN_SP),INTENT(IN) :: N
39 C> Total number of indices
40  INTEGER(GRIDMAN_SP),INTENT(IN) :: L
41 C> Error code
42  INTEGER,INTENT(OUT) :: IERR
43 
44  INTEGER :: ST
45 
46  IF(gridman_dbg)
47  w WRITE(gridman_unit,*) "Starting GRIDMAN_INDLIST_ALLOCATE"
48 
49  ierr=0
50 
51  IF(n.LT.1.OR.l.LT.1.OR.n.GT.l) THEN
52  ierr=100
53  WRITE(gridman_unit,*) "ERROR in GRIDMAN_INDLIST_ALLOCATE: ",
54  w "incorrect array size"
55  WRITE(gridman_unit,*) " N, L ",n,l
56  RETURN
57  END IF
58 
59  CALL gridman_indlist_deallocate(indlist,ierr)
60  IF(ierr.NE.0) THEN
61  WRITE(gridman_unit,*) "GRIDMAN_INDLIST_ALLOCATE terminated"
62  RETURN
63  END IF
64 
65  indlist%N=n
66  indlist%L=l
67 
68  ALLOCATE(indlist%IFIRST(n),stat=st)
69  IF(st.NE.0) THEN
70  ierr=200
71  WRITE(gridman_unit,*) "ERROR in GRIDMAN_INDLIST_ALLOCATE: ",
72  w "cannot allocate array IFIRST"
73  WRITE(gridman_unit,*) " N ",n
74  RETURN
75  END IF
76 
77  ALLOCATE(indlist%ILAST(n),stat=st)
78  IF(st.NE.0) THEN
79  ierr=200
80  WRITE(gridman_unit,*) "ERROR in GRIDMAN_INDLIST_ALLOCATE: ",
81  w "cannot allocate array ILAST"
82  WRITE(gridman_unit,*) " N ",n
83  RETURN
84  END IF
85 
86  ALLOCATE(indlist%IND(l),stat=st)
87  IF(st.NE.0) THEN
88  ierr=200
89  WRITE(gridman_unit,*) "ERROR in GRIDMAN_INDLIST_ALLOCATE: ",
90  w "cannot allocate array IND"
91  WRITE(gridman_unit,*) " L ",l
92  RETURN
93  END IF
94 
95 
96  IF(gridman_dbg)
97  w WRITE(gridman_unit,*) "GRIDMAN_INDLIST_ALLOCATE finished"
98 
99 
100  END SUBROUTINE gridman_indlist_allocate
101 
102 C *****************************************************************************************
103 C> Deallocate list of indices
104 C *****************************************************************************************
105  SUBROUTINE gridman_indlist_deallocate(INDLIST,IERR)
107  IMPLICIT NONE
108 C> List of indices to be deallocated
109  TYPE(gridman_indlist) :: INDLIST
110 C> Error code
111  INTEGER,INTENT(OUT) :: IERR
112 
113  INTEGER :: ST
114 
115  IF(gridman_dbg)
116  w WRITE(gridman_unit,*) "Starting GRIDMAN_INDLIST_DEALLOCATE"
117 
118  ierr=0
119 
120  IF(ALLOCATED(indlist%IND)) THEN
121  DEALLOCATE(indlist%IND,stat=st)
122  IF(st.NE.0) THEN
123  ierr=-200
124  WRITE(gridman_unit,*)
125  w "WARNING from GRIDMAN_INDLIST_DEALLOCATE: ",
126  w "can not deallocate IND"
127  END IF
128  END IF
129 
130  IF(ALLOCATED(indlist%IFIRST)) THEN
131  DEALLOCATE(indlist%IFIRST,stat=st)
132  IF(st.NE.0) THEN
133  ierr=-200
134  WRITE(gridman_unit,*)
135  w "WARNING from GRIDMAN_INDLIST_DEALLOCATE: ",
136  w "can not deallocate IEDGESS"
137  END IF
138  END IF
139 
140  IF(ALLOCATED(indlist%ILAST)) THEN
141  DEALLOCATE(indlist%ILAST,stat=st)
142  IF(st.NE.0) THEN
143  ierr=-200
144  WRITE(gridman_unit,*)
145  w "WARNING from GRIDMAN_INDLIST_DEALLOCATE: ",
146  w "can not deallocate ILAST"
147  END IF
148  END IF
149 
150  indlist%N=0
151  indlist%L=0
152 
153  IF(gridman_dbg)
154  w WRITE(gridman_unit,*) "GRIDMAN_CELLS_DEALLOCATE finished"
155 
156  END SUBROUTINE gridman_indlist_deallocate
subroutine gridman_indlist_allocate(INDLIST, N, L, IERR)
Allocate list of elements.
Definition: indlist.f:32
integer, save, public gridman_unit
Index of the standard output unit.
Definition: gridman.f:116
subroutine gridman_indlist_deallocate(INDLIST, IERR)
Deallocate list of indices.
Definition: indlist.f:106
logical, save, public gridman_dbg
Switch for debugging mode.
Definition: gridman.f:122
Data-type which describes lists of elements with variable number of indices for each element...
Definition: gridman.f:225
Definition of data types, global constants and variables.
Definition: gridman.f:83
integer, parameter, public gridman_sp
Kind parameter for integer numbers.
Definition: gridman.f:95