The TELEMAC-MASCARET system  trunk
deall_bief.f
Go to the documentation of this file.
1 ! *********************
2  SUBROUTINE deall_bief
3 !
4 !***********************************************************************
5 ! BIEF V7P0
6 !***********************************************************************
7 !
8 !brief CLEAN UP THE DATA FROM BIEF
9 !
10 !history Y AUDOUIN (LNHE)
11 !+ 21/05/2015
12 !+ V7P1
13 !+
14 !
15 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
16 !| MESH |-->| THE MESH TO BE DEALLOCATED
17 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
18 !
19  USE bief,ex_deall_bief=>deall_bief
21  USE algae_transp, ONLY: dealloc_algae
23 !
25  IMPLICIT NONE
26 !
27 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
28 !
29 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
30 !
31  INTEGER :: I
32 ! Old saved variables
33 !
34  ! solve
35  IF(.NOT.first_solve) THEN
36  CALL bief_deallobj(tbb)
37  ! BB contains link to array that are deallocated by the module
38  ! using solve
39  DO i=1,bb%N
40  NULLIFY(bb%ADR(i)%P)
41  ENDDO
42  CALL bief_deallobj(bb)
43  ! Same with BX
44  DO i=1,bx%N
45  NULLIFY(bx%ADR(i)%P)
46  ENDDO
47  CALL bief_deallobj(bx)
48  first_solve = .true.
49  ENDIF
50  ! CVTRVF_POS_2
51  IF(deja_cpos2) THEN
52  DEALLOCATE(indic_cpos2)
53  deja_cpos2=.false.
54  ENDIF
55  ! POSITIVE_DEPTHS
56  IF(deja_pdept_nerd) THEN
57  DEALLOCATE(indic_pdept_nerd)
58  deja_pdept_nerd=.false.
59  ENDIF
60  IF(deja_pdept_eria) THEN
61  DEALLOCATE(indic_pdept_eria)
62  deja_pdept_eria=.false.
63  ENDIF
64  ! CVTRVF_POS
65  IF(deja_cpos) THEN
66  DEALLOCATE(indic_cpos)
67  deja_cpos=.false.
68  ENDIF
69  ! SD_SOLVE_1
70  IF(size_in.NE.0) THEN
71  DEALLOCATE(in_ss1)
72  size_in = 0
73  ENDIF
74  IF(size_ip.NE.0) THEN
75  DEALLOCATE(ip_ss1)
76  size_ip = 0
77  ENDIF
78  IF(size_isegip.NE.0) THEN
79  DEALLOCATE(isegip_ss1)
80  size_isegip = 0
81  ENDIF
82  IF(size_iw1.NE.0) THEN
83  DEALLOCATE(iw1_ss1)
84  size_iw1 = 0
85  ENDIF
86  IF(size_indtri.NE.0) THEN
87  DEALLOCATE(indtri_ss1)
88  size_indtri = 0
89  ENDIF
90  IF(size_inx.NE.0) THEN
91  DEALLOCATE(inx_ss1)
92  size_inx = 0
93  ENDIF
94  IF(size_ipx.NE.0) THEN
95  DEALLOCATE(ipx_ss1)
96  size_ipx = 0
97  ENDIF
98  IF(size_ac.NE.0) THEN
99  DEALLOCATE(ac_ss1)
100  size_ac = 0
101  ENDIF
102  IF(size_actri.NE.0) THEN
103  DEALLOCATE(actri_ss1)
104  size_actri = 0
105  ENDIF
106  IF(size_isp.NE.0) THEN
107  DEALLOCATE(isp_ss1)
108  size_isp = 0
109  ENDIF
110  IF(size_rsp.NE.0) THEN
111  DEALLOCATE(rsp_ss1)
112  size_rsp = 0
113  ENDIF
114  ! SD_SOLVE_4
115  IF(size_gloseg4.NE.0) THEN
116  DEALLOCATE(gloseg4_ss4)
117  size_gloseg4 = 0
118  ENDIF
119  IF(size_da.NE.0) THEN
120  DEALLOCATE(da_ss4)
121  size_da = 0
122  ENDIF
123  IF(size_xa.NE.0) THEN
124  DEALLOCATE(xa_ss4)
125  size_xa = 0
126  ENDIF
127  IF(size_rhs.NE.0) THEN
128  DEALLOCATE(rhs_ss4)
129  size_rhs = 0
130  ENDIF
131  IF(size_xinc.NE.0) THEN
132  DEALLOCATE(xinc_ss4)
133  size_xinc = 0
134  ENDIF
135  ! PRE4_MUMPS
136  IF(size_gloseg4_p4m.NE.0) THEN
137  DEALLOCATE(gloseg4_p4m)
138  size_gloseg4_p4m = 0
139  ENDIF
140  IF(size_da_p4m.NE.0) THEN
141  DEALLOCATE(da_p4m)
142  size_da_p4m = 0
143  ENDIF
144  IF(size_xa_p4m.NE.0) THEN
145  DEALLOCATE(xa_p4m)
146  size_xa_p4m = 0
147  ENDIF
148  IF(size_rhs_p4m.NE.0) THEN
149  DEALLOCATE(rhs_p4m)
150  size_rhs_p4m = 0
151  ENDIF
152  IF(size_xinc_p4m.NE.0) THEN
153  DEALLOCATE(xinc_p4m)
154  size_xinc_p4m = 0
155  ENDIF
156  ! CHARAC
157  IF(deja_charac) THEN
158  CALL bief_deallobj(t1weak)
159  CALL bief_deallobj(t2weak)
160  CALL bief_deallobj(t3weak)
161  CALL bief_deallobj(t4weak)
162  CALL bief_deallobj(t5weak)
163  CALL bief_deallobj(t6weak)
164  CALL bief_deallobj(t7weak)
165  CALL bief_deallobj(shpwea)
167  CALL bief_deallobj(shpbuf)
168  CALL bief_deallobj(shzbuf)
169  CALL bief_deallobj(shzwea)
170  deja_charac = .false.
171  ENDIF
172  ! DERIVE
173  IF(deja_derive) THEN
175  deja_derive = .false.
176  ENDIF
177  IF(.NOT.init_alg) THEN
178  DEALLOCATE(buff_1d_d)
179  DEALLOCATE(buff_2d_d)
180  ENDIF
181 !
182 ! Streamline
183 !
184  CALL dealloc_streamline()
185 
186 !
187 ! Algae
188 !
189  CALL dealloc_algae()
190 !
191 ! Gracjg
192 !
193  gracjg_cnt = 0
194 
195 !
196 !-----------------------------------------------------------------------
197 !
198  RETURN
199  END
integer, dimension(:), allocatable indic_cpos2
integer, dimension(:), allocatable isp_ss1
integer, dimension(:), allocatable inx_ss1
integer, dimension(:), allocatable gloseg4_ss4
double precision, dimension(:), allocatable rsp_ss1
type(bief_obj), target t3weak
type(bief_obj), target shpwea
type(bief_obj), target shpbuf
subroutine bief_deallobj(OBJ)
Definition: bief_deallobj.f:7
integer, dimension(:), allocatable ip_ss1
double precision, dimension(:), allocatable da_p4m
double precision, dimension(:), allocatable da_ss4
double precision, dimension(:), allocatable ac_ss1
double precision, dimension(:), allocatable actri_ss1
double precision, dimension(:,:), allocatable buff_2d_d
integer, dimension(:), allocatable indtri_ss1
double precision, dimension(:), allocatable rhs_ss4
double precision, dimension(:), allocatable xinc_p4m
integer, dimension(:), allocatable iw1_ss1
double precision, dimension(:), allocatable xa_ss4
type(bief_obj), target t5weak
subroutine, public dealloc_streamline
Definition: streamline.f:301
type(bief_obj), target shzwea
type(bief_obj), target t7weak
type(bief_obj), target t2weak
integer, dimension(:), allocatable in_ss1
type(bief_obj), target t6weak
double precision, dimension(:), allocatable rhs_p4m
type(bief_obj), target bx
type(bief_obj), target t1weak
integer, dimension(:), allocatable isegip_ss1
double precision, dimension(:), allocatable xinc_ss4
integer, dimension(:), allocatable ipx_ss1
double precision, dimension(:), allocatable xa_p4m
integer, dimension(:), allocatable indic_pdept_eria
subroutine, public dealloc_algae()
integer, dimension(:), allocatable indic_cpos
integer, dimension(:), allocatable indic_pdept_nerd
double precision, dimension(:), allocatable buff_1d_d
integer, dimension(:), allocatable gloseg4_p4m
type(bief_obj), target bb
type(bief_obj), target ftild_weak
subroutine deall_bief
Definition: deall_bief.f:4
type(bief_obj), target shzbuf
Definition: bief.f:3
type(bief_obj), target t4weak