OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_preread_node.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "scr17_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_node (unitab, lsubmodel, numnusr, is_dyna)

Function/Subroutine Documentation

◆ hm_preread_node()

subroutine hm_preread_node ( type (unit_type_), intent(in) unitab,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel,
integer, intent(in) numnusr,
integer, intent(in) is_dyna )

Definition at line 37 of file hm_preread_node.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE unitab_mod
42 USE message_mod
46 USE reader_old_mod , ONLY : line
47 USE user_id_mod , ONLY : id_limit
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "com04_c.inc"
56#include "scr17_c.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 TYPE (UNIT_TYPE_),INTENT(IN) :: UNITAB
61 TYPE(SUBMODEL_DATA),INTENT(IN):: LSUBMODEL(NSUBMOD)
62 INTEGER,INTENT(IN) :: NUMNUSR
63 INTEGER,INTENT(IN) :: IS_DYNA
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER N,I,J,IERROR, STAT
68 INTEGER FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP,IFLAGUNIT, UID, ID
69 my_real fac_l
70 INTEGER, DIMENSION(:), ALLOCATABLE :: SUB_NOD,UID_NOD
71 INTEGER, DIMENSION(:), ALLOCATABLE :: ITAB
72 my_real, DIMENSION(:,:), ALLOCATABLE :: x
73 real*8, DIMENSION(:,:), ALLOCATABLE :: hm_x
74 real*8, DIMENSION(:), ALLOCATABLE :: dmerge
75 CHARACTER(LEN=NCHARFIELD) :: KEY
76 LOGICAL IS_AVAILABLE
77C-----------------------------------------------
78 fac_l = one
79C--------------------------------------------------
80C ALLOCS & INITS
81C--------------------------------------------------
82 ALLOCATE (itab(numnusr+numcnod),stat=stat)
83 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='ITAB')
84 ALLOCATE (x(3,numnusr+numcnod),stat=stat)
85 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='X')
86 ALLOCATE (sub_nod(numnusr+numcnod),stat=stat)
87 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='SUB_NOD')
88 ALLOCATE (uid_nod(numnusr+numcnod),stat=stat)
89 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='UID_NOD')
90 ALLOCATE (hm_x(3,numnusr+numcnod),stat=stat)
91 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='HM_X')
92 ALLOCATE (dmerge(numcnod),stat=stat)
93 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,msgtype=msgerror,c1='DMERGE')
94 sub_nod(1:numnusr+numcnod) = 0
95 uid_nod(1:numnusr+numcnod) = 0
96 dmerge(1:numcnod) = zero
97C--------------------------------------------------
98C PRE-LECTURE DES NODES INPUTS DANS HM STRUCTURE
99C--------------------------------------------------
100 CALL cpp_nodes_read(itab,hm_x,dmerge,sub_nod,uid_nod)
101C--------------------------------------------------
102C FILL OTHER STRUCTURES + CHECKS
103C--------------------------------------------------
104 uid = -1
105 n=0
106 DO i=1,numnusr+numcnod
107 n=n+1
108 x(1,n) = hm_x(1,n)
109 x(2,n) = hm_x(2,n)
110 x(3,n) = hm_x(3,n)
111C--------------------------------------------------
112 IF(sub_nod(n) /= 0)THEN
113 IF(uid_nod(n) == 0 .AND. lsubmodel(sub_nod(n))%UID /= 0) uid_nod(n) = lsubmodel(sub_nod(n))%UID
114 ENDIF
115 IF ( itab(n) > id_limit%GLOBAL )THEN
116 CALL ancmsg(msgid=509,anmode=aninfo,msgtype=msgerror,i1=itab(n),c1=line,c2='/NODE')
117 ENDIF
118C--------------------------------------------------
119C UNITS
120C--------------------------------------------------
121 IF(uid_nod(n) /= uid )THEN
122 uid = uid_nod(n)
123 iflagunit = 0
124 DO j=1,unitab%NUNITS
125 IF (unitab%UNIT_ID(j) == uid) THEN
126 fac_l = unitab%FAC_L(j)
127 iflagunit = 1
128 EXIT
129 ENDIF
130 ENDDO
131 IF (uid/=0 .AND. iflagunit==0 .AND. i <= numnusr)THEN
132 CALL ancmsg(msgid=643,anmode=aninfo,msgtype=msgerror,i1=uid,c1='/NODE')
133 ELSEIF (uid/=0 .AND. iflagunit==0 .AND. i > numnusr)THEN
134 CALL ancmsg(msgid=643,anmode=aninfo,msgtype=msgerror,i1=uid,c1='/CNODE')
135 ENDIF
136 ENDIF
137 x(1,n) = x(1,n)*fac_l
138 x(2,n) = x(2,n)*fac_l
139 x(3,n) = x(3,n)*fac_l
140 ENDDO
141 IF(ALLOCATED(sub_nod)) DEALLOCATE(sub_nod)
142 IF(ALLOCATED(uid_nod)) DEALLOCATE(uid_nod)
143 IF(ALLOCATED(hm_x)) DEALLOCATE(hm_x)
144 IF(ALLOCATED(dmerge)) DEALLOCATE(dmerge)
145C--------------------------------------------------
146C Check nodes within some tolerance (possibly merge nodes)
147C--------------------------------------------------
148 CALL auto_node_merge(is_dyna,numnusr,numcnod,numnod,itab,x)
149C--------------------------------
150 DEALLOCATE(itab,x)
151 RETURN
152C--------------------------------
subroutine auto_node_merge(is_dyna, numnusr, numcnod, numnod, itab, x)
#define my_real
Definition cppsort.cpp:32
integer, parameter ncharfield
integer nsubmod
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)
Definition message.F:889