39
40
41
45 USE parith_on_mod
46
47
48
49#include "implicit_f.inc"
50
51
52
53#include "com01_c.inc"
54#include "scr18_c.inc"
55#include "parit_c.inc"
56#include "tabsiz_c.inc"
57
58
59
60 INTEGER NEW_COUNT,CALL_ID
61 INTEGER, INTENT(IN) :: INTHEAT
62 INTEGER, INTENT(IN) :: NODADT_THERM
63 TYPE(INTERFACE_PON_), INTENT(INOUT) :: PON
64
65
66
67 INTEGER IERROR
68 INTEGER SISKY_OLD,LSKYI_OLD
69 CHARACTER MSG*50,ID*50
70 my_real,
DIMENSION(:,:),
ALLOCATABLE :: temp_fskyi_ply
71 INTEGER, DIMENSION(:),ALLOCATABLE :: TEMP_ISKY
72 my_real,
dimension(:,:),
allocatable :: temp_fskyi
73
74
75
76
77
78
79
80
81
82
83
84 WRITE(
id,
'(I2.2)') call_id
85 msg=
'(/PARITH/ON) - '//
id(1:2)
86 sisky_old = sisky
87 lskyi_old = lskyi
88
89
90
91
92 ALLOCATE(temp_fskyi(lskyi,nfskyi),stat=ierror)
93 IF(ierror/=0) THEN
94 CALL ancmsg(msgid=19,anmode=aninfo,
95 . c1=msg)
97 ENDIF
98 temp_fskyi(1:nisky,1:nfskyi)=pon%FSKYI(1:nisky,1:nfskyi)
99 DEALLOCATE(pon%FSKYI)
100
101
102
103
104 ALLOCATE(temp_isky(sisky),stat=ierror)
105 IF(ierror/=0) THEN
106 CALL ancmsg(msgid=19,anmode=aninfo,
107 . c1=msg)
109 ENDIF
110 temp_isky(1:nisky)=pon%ISKY(1:nisky)
111 DEALLOCATE(pon%ISKY)
112
113
114
115
116 IF(intheat > 0 ) THEN
117 ALLOCATE(temp_ftheskyi(lskyi),stat=ierror)
118 IF(ierror/=0) THEN
119 CALL ancmsg(msgid=19,anmode=aninfo,
120 . c1=msg)
122 ENDIF
123 temp_ftheskyi(1:nisky)=ftheskyi(1:nisky)
124 DEALLOCATE(ftheskyi)
125 IF(nodadt_therm ==1) THEN
126 ALLOCATE(temp_condnskyi(lskyi))
127 temp_condnskyi(1:lskyi)=condnskyi(1:lskyi)
128 DEALLOCATE(condnskyi)
129 ENDIF
130 ENDIF
131
132
133
134 lskyi = nint( (lskyi+new_count)*1.2 )
135 sisky = lskyi
136 sfskyi = lskyi*nfskyi
137
138
139 ALLOCATE(pon%FSKYI(lskyi,nfskyi),stat=ierror)
140 IF(ierror/=0) THEN
141 CALL ancmsg(msgid=19,anmode=aninfo,
142 . c1=msg)
144 ENDIF
145 pon%FSKYI(1:lskyi_old,1:nfskyi)=temp_fskyi(1:lskyi_old,1:nfskyi)
146 DEALLOCATE(temp_fskyi)
147
148
149
150 ALLOCATE(pon%ISKY(sisky),stat=ierror)
151 IF(ierror/=0) THEN
152 CALL ancmsg(msgid=19,anmode=aninfo,
153 . c1=msg)
155 ENDIF
156 pon%ISKY(1:sisky_old) = temp_isky(1:sisky_old)
157 DEALLOCATE(temp_isky)
158
159
160 IF(intheat > 0 ) THEN
161 ALLOCATE(ftheskyi(lskyi),stat=ierror)
162 IF(ierror/=0) THEN
163 CALL ancmsg(msgid=19,anmode=aninfo,
164 . c1=msg)
166 ENDIF
167 ftheskyi(1:lskyi_old)=temp_ftheskyi(1:lskyi_old)
168 DEALLOCATE (temp_ftheskyi)
169
170 IF(nodadt_therm ==1) THEN
171 ALLOCATE(condnskyi(lskyi))
172 condnskyi(1:lskyi_old)=temp_condnskyi(1:lskyi_old)
173 DEALLOCATE (temp_condnskyi)
174
175 ENDIF
176 ENDIF
177
178
179
180 IF(intplyxfem > 0) THEN
181
182 ALLOCATE(temp_fskyi_ply(lskyi_old,5))
183 temp_fskyi_ply(1:lskyi_old,1:5) =
plyskyi%FSKYI(1:lskyi_old,1:5)
185
186 ALLOCATE(
plyskyi%FSKYI(lskyi,5))
188 plyskyi%FSKYI(1:lskyi_old,1:5)=temp_fskyi_ply(1:lskyi_old,1:5)
189 DEALLOCATE(temp_fskyi)
190 ENDIF
191
192
type(ply_data), allocatable plyskyi
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)