51 USE reader_old_mod ,
ONLY : line, irec
52 USE user_id_mod ,
ONLY : id_limit
56#include "implicit_f.inc"
61#include "remesh_c.inc"
68 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
72 INTEGER,
DIMENSION(:),
ALLOCATABLE :: ITAB,ITABM1,KNOD2SH,NOD2SH
73 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: IXC,IXTG,TAG
74 INTEGER IPART(4,NPART),
75 . N,IP,ID,I,J,NLEV,NMUL,STAT,INDEX_PART,
76 INTEGER USR2SYS,NUMNUSR1,IDS,NI,NJ,NK,NL,K,L,P,Q,QQ,
79CHARACTER(LEN=NCHARTITLE) :: TITR
80 CHARACTER(LEN=NCHARKEY) :: KEY
81 INTEGER ,
DIMENSION(:),
ALLOCATABLE :: IPARTC, SHELL_ID
82 INTEGER ,
DIMENSION(:),
ALLOCATABLE :: IPARTTG, SH3N_ID
83 real*8 ,
DIMENSION(:),
ALLOCATABLE :: sh_angle, sh_thk
84 real*8 ,
DIMENSION(:),
ALLOCATABLE :: sh3_angle, sh3_thk
85 INTEGER,
DIMENSION(:),
ALLOCATABLE :: SUBID_SHELL,
86 INTEGER,
DIMENSION(:),
ALLOCATABLE :: SUBID_SH3N,UID_SH3N
87 INTEGER,
DIMENSION(:),
ALLOCATABLE :: SUBID_NODES
91 DATA mess /
'OPTIONS FOR ADAPTIVE MESHING DEFINITION '/
95 ALLOCATE(itab(numnusr),itabm1(2*numnusr),
96 . ixc(nixc,numelc0),ixtg(nixtg,numeltg0),
97 . knod2sh(0:numnusr),nod2sh(4*numelc0+3*numeltg0),
98 . tag(4,numelc0+numeltg0))
116 . option_titr = titr)
131 . option_titr = titr,
135 is_available = .false.
139 CALL hm_get_intv(
'LEVEL',levelmax,is_available,lsubmodel)
140 CALL hm_get_intv(
'Iadmrule',iadmrule,is_available,lsubmodel)
141 CALL hm_get_intv(
'Istatcnd',istatcnd,is_available,lsubmodel)
145 CALL hm_get_floatv(
'Tdelay',dtadmesh,is_available,lsubmodel,unitab)
150 IF(nadmeshstat > 0) iadmstat = 1
152 IF(iadmstat /= 0) id_limit%ADMESH=id_limit%GLOBAL
166 . option_titr = titr,
169 is_available = .false.
173 CALL hm_get_intv(
'NIP',npart_adm,is_available,lsubmodel)
182 IF(ipart(1,j)==id_ip)
THEN
206 ALLOCATE (ipartc(numelc))
207 ALLOCATE (sh_angle(numelc))
208 ALLOCATE (sh_thk(numelc))
212 ALLOCATE (subid_shell(numelc),stat=stat)
213 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
216 ALLOCATE (uid_shell(numelc),stat=stat)
217 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
220 subid_shell(1:numelc) = 0
221 uid_shell(1:numelc) = 0
227 CALL cpp_shell_read(ixc,nixc,ipartc,sh_angle,sh_thk,subid_shell,uid_shell)
237 IF( ipartc(i) /= ip0)
THEN
239 IF(ipartc(i) == ipart(1,j))
THEN
253 ipart(2,ip)=ipart(2,ip)+1
257 IF(
ALLOCATED(subid_shell))
DEALLOCATE(subid_shell)
258 IF(
ALLOCATED(uid_shell))
DEALLOCATE(uid_shell)
260 ALLOCATE (iparttg(numeltg))
261 ALLOCATE (sh3_angle(numeltg))
262 ALLOCATE (sh3_thk(numeltg))
266 ALLOCATE (subid_sh3n(numeltg),stat=stat)
267 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
270 ALLOCATE (uid_sh3n(numeltg),stat=stat)
271 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
274 subid_sh3n(1:numeltg) = 0
275 uid_sh3n(1:numeltg) = 0
281 CALL cpp_sh3n_read(ixtg,nixtg,iparttg,sh3_angle,sh3_thk,subid_sh3n,uid_sh3n)
291 IF( iparttg(i) /= ip0)
THEN
293 IF(iparttg(i) == ipart(1,j))
THEN
306 ipart(3,ip)=ipart(3,ip)+1
310 IF(
ALLOCATED(subid_sh3n))
DEALLOCATE(subid_sh3n)
311 IF(
ALLOCATED(uid_sh3n))
DEALLOCATE(uid_sh3n)
315 IF(iadmstat /= 0)
RETURN
319 ALLOCATE (subid_nodes(numnusr),stat=stat)
320 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
323 subid_nodes(1:numnusr) = 0
327 CALL cpp_node_count(numnusr1)
328 CALL cpp_node_id_read(itab,subid_nodes)
333 IF (itab(i) > id_limit%ADMESH
334 . .AND. (itab(i) < id_limit%ADMESH_FT_NODE_AUTO .OR. itab(i) >= id_limit%ADMESH_LT_NODE_AUTO))
THEN
335 CALL ancmsg(msgid=1069,anmode=aninfo,msgtype=msgerror,i1=itab(i),c1=line,c2=
'/NODE')
338 IF(
ALLOCATED(subid_nodes))
DEALLOCATE(subid_nodes)
343 CALL constit(itab,itabm1,numnusr)
348 IF (ixc(nixc,i)>id_limit%ADMESH)
THEN
349 CALL ancmsg(msgid=1069,anmode=aninfo,msgtype=msgerror,
350 . i1=ixc(nixc,i),c1=line,c2=
'/SHELL')
353 ixc(j,i)=usr2sys(ixc(j,i),itabm1,mess,id)
356 IF(
ALLOCATED(ipartc))
DEALLOCATE(ipartc)
357 IF(
ALLOCATED(sh_angle))
DEALLOCATE(sh_angle)
358 IF(
ALLOCATED(sh_thk))
DEALLOCATE (sh_thk)
361 IF (ixtg(nixtg,i)>id_limit%ADMESH)
THEN
362 CALL ancmsg(msgid=1069,anmode=aninfo,msgtype=msgerror,
363 . i1=ixtg(nixtg,i),c1=line,c2=
'/SH3N')
366 ixtg(j,i)=usr2sys(ixtg(j,i),itabm1,mess,id)
369 IF(
ALLOCATED(iparttg))
DEALLOCATE(iparttg)
370 IF(
ALLOCATED(sh3_angle))
DEALLOCATE (sh3_angle)
371 IF(
ALLOCATED(sh3_thk))
DEALLOCATE (sh3_thk)
379 knod2sh(ni)=knod2sh(ni)+1
386 knod2sh(ni)=knod2sh(ni)+1
391 knod2sh(n)=knod2sh(n)+knod2sh(n-1)
397 knod2sh(ni)=knod2sh(ni)+1
398 nod2sh(knod2sh(ni))=n
405 knod2sh(ni)=knod2sh(ni)+1
406 nod2sh(knod2sh(ni))=numelc0+n
411 knod2sh(n)=knod2sh(n-1)
422 numnod=numnod+(2**nlev-1)*(2**nlev-1)
424 IF(tag(i,n)<nlev)
THEN
425 numnod=numnod+(2**nlev-1)-(2**(tag(i,n
430 DO k=knod2sh(ni-1)+1,knod2sh(ni)
433 DO l=knod2sh(nj-1)+1,knod2sh(nj)
440 IF((nk==ni.AND.nl==nj).OR.
441 . (nl==ni.AND.nk==nj))
THEN
449 nl=ixtg(mod(j,3)+2,qq)
450 IF((nk==ni.AND.nl==nj).OR.
451 . (nl==ni.AND.nk==nj))
THEN
463 numelc =numelc +(4**(nlev+1)-1)/3
472 numnod =numnod+(2**(nlev-1)+1)*(2**nlev+1)-3*(2**nlev)
474 IF(tag(i,n+numelc0)<nlev)
THEN
475 numnod=numnod+(2**nlev-1)-(2**(tag(i,n+numelc0))-1)
476 tag(i,n+numelc0)=nlev
479 nj=ixtg(mod(i,3)+2,n)
480 DO k=knod2sh(ni-1)+1,knod2sh(ni)
483 DO l=knod2sh(nj-1)+1,knod2sh(nj)
490 IF((nk==ni.AND.nl==nj).OR.
491 . (nl==ni.AND.nk==nj))
THEN
499 nl=ixtg(mod(j,3)+2,qq)
500 IF((nk==ni.AND.nl==nj).OR.
501 . (nl==ni.AND.nk==nj))
THEN
513 numeltg =numeltg +(4**(nlev+1)-1)/3
516 DEALLOCATE(itab,itabm1,ixc,ixtg,knod2sh,nod2sh,tag)
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)