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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_initemp (temp, nintemp, itherm_fe, itab, itabm1, igrnod, initids, unitab, lsubmodel)

Function/Subroutine Documentation

◆ hm_read_initemp()

subroutine hm_read_initemp ( temp,
integer, intent(in) nintemp,
integer, intent(in) itherm_fe,
integer, dimension(*) itab,
integer, dimension(*) itabm1,
type (group_), dimension(ngrnod) igrnod,
integer, dimension(*) initids,
type (unit_type_), intent(in) unitab,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 43 of file hm_read_initemp.F.

45C-----------------------------------------------
46C M o d u l e s
47C-----------------------------------------------
48 USE unitab_mod
49 USE message_mod
50 USE groupdef_mod
51 USE submodel_mod
54C-----------------------------------------------
55C I m p l i c i t T y p e s
56C-----------------------------------------------
57#include "implicit_f.inc"
58C-----------------------------------------------
59C C o m m o n B l o c k s
60C-----------------------------------------------
61#include "com01_c.inc"
62#include "com04_c.inc"
63C-----------------------------------------------
64C D u m m y A r g u m e n t s
65C-----------------------------------------------
66 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
67 INTEGER ITAB(*), ITABM1(*),INITIDS(*)
68 INTEGER ,INTENT(IN) :: NINTEMP
69 INTEGER ,INTENT(IN) :: ITHERM_FE
70 my_real :: temp(*)
71 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
72C-----------------------------------------------
73 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
74C-----------------------------------------------
75C L o c a l V a r i a b l e s
76C-----------------------------------------------
77 INTEGER I,J,N,NNOD,NOSYS,ITYPE,ID,ISK,IGR,IGRS,NBTEMP,BID,
78 . FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP,UID,TYP,NOD,NODSYS,NB_LINE
80 . temp0
81 CHARACTER MESS*40
82 CHARACTER(LEN=NCHARTITLE) :: TITR
83 CHARACTER(LEN=NCHARKEY) :: KEY
84 LOGICAL IS_AVAILABLE
85 my_real, DIMENSION(:), ALLOCATABLE :: list_temp0
86 INTEGER, DIMENSION(:), ALLOCATABLE :: LIST_NOD
87C-----------------------------------------------
88C E x t e r n a l F u n c t i o n s
89C-----------------------------------------------
90 INTEGER USR2SYS, USRTOS
91 DATA mess/'INITIAL TEMPERATURE DEFINITION '/
92C=======================================================================
93 bid =0
94 nbtemp = 0
95 is_available = .false.
96 nb_line = 0
97C--------------------------------------------------
98C START BROWSING MODEL INITEMP
99C--------------------------------------------------
100 CALL hm_option_start('/INITEMP')
101C--------------------------------------------------
102C BROWSING /INITEMP OPTIONS 1->NRADIA
103C--------------------------------------------------
104 DO i=1,nintemp
105 titr = ''
106 CALL hm_option_read_key(lsubmodel,
107 . unit_id = uid,
108 . option_id = id,
109 . option_titr = titr)
110
111! IF (ITHERM_FE == 0) THEN
112! CALL ANCMSG(MSGID=858,
113! . MSGTYPE=MSGERROR,
114! . ANMODE=ANINFO)
115! ENDIF
116C--------------------------------------------------
117C EXTRACT DATAS (INTEGER VALUES)
118C--------------------------------------------------
119 CALL hm_get_intv('distribution',typ,is_available,lsubmodel)
120 CALL hm_get_intv('entityid',igr,is_available,lsubmodel)
121 IF (typ == 1) THEN
122 CALL hm_get_intv('grnd_ID',igr,is_available,lsubmodel)
123 CALL hm_get_intv('distribution_table_count',nb_line,is_available,lsubmodel)
124 IF(.NOT.ALLOCATED(list_nod)) ALLOCATE(list_nod(nb_line))
125 list_nod(1:nb_line) = 0
126 IF(.NOT.ALLOCATED(list_temp0)) ALLOCATE(list_temp0(nb_line))
127 list_temp0(1:nb_line) = zero
128 DO j=1,nb_line
129 CALL hm_get_int_array_index('location_unit_node',list_nod(j),j,is_available,lsubmodel)
130 ENDDO
131 ENDIF
132C--------------------------------------------------
133C EXTRACT DATAS (REAL VALUES)
134C--------------------------------------------------
135 IF (typ == 0) THEN
136 CALL hm_get_floatv('magnitude',temp0,is_available,lsubmodel,unitab)
137 ELSEIF (typ == 1) THEN
138 CALL hm_get_float_array_index('T0',temp0,j,is_available,lsubmodel,unitab)
139 DO j=1,nb_line
140 CALL hm_get_float_array_index('magnitude',list_temp0(j),j,is_available,lsubmodel,unitab)
141 ENDDO
142 ENDIF
143C--------------------------------------------------
144 nbtemp = nbtemp+1
145 initids(nbtemp)=id
146 igrs=0
147 IF (typ == 0) THEN
148 IF (igr == 0)THEN
149 CALL ancmsg(msgid=668,
150 . msgtype=msgerror,
151 . anmode=aninfo,
152 . c1='/INITEM',
153 . c2='/INITEM',
154 . c3=titr,
155 . i1=id)
156 ENDIF
157 DO j=1,ngrnod
158 IF (igr == igrnod(j)%ID) igrs=j
159 ENDDO
160 IF(igrs /= 0)THEN
161 DO j=1,igrnod(igrs)%NENTITY
162 nosys=igrnod(igrs)%ENTITY(j)
163 temp(nosys)= temp0
164 ENDDO
165 nnod=igrnod(igrs)%NENTITY
166 ELSE
167 CALL ancmsg(msgid=53,
168 . msgtype=msgerror,
169 . anmode=aninfo,
170 . c1='IN /INITEM OPTION',
171 . i1=igr)
172 ENDIF
173 ELSE
174 DO j=1,ngrnod
175 IF (igr == igrnod(j)%ID) igrs=j
176 ENDDO
177 IF(igrs /= 0)THEN
178 DO j=1,igrnod(igrs)%NENTITY
179 nosys=igrnod(igrs)%ENTITY(j)
180 temp(nosys)= temp0
181 ENDDO
182 nnod=igrnod(igrs)%NENTITY
183 ENDIF
184 DO j=1,nb_line
185 nodsys=usr2sys(list_nod(j),itabm1,mess,id)
186 IF (list_nod(j) == 0) THEN
187 CALL ancmsg(msgid=78,
188 . msgtype=msgerror,
189 . anmode=aninfo,
190 . c1='/INITEM',
191 . i1=id,
192 . i2=nod)
193 ENDIF
194 IF (nodsys /= 0) temp(nodsys)= list_temp0(j)
195 ENDDO
196 ENDIF
197 IF(ALLOCATED(list_temp0)) DEALLOCATE(list_temp0)
198 IF(ALLOCATED(list_nod)) DEALLOCATE(list_nod)
199 ENDDO
200C---
201 CALL udouble(initids,1,nbtemp,mess,0,bid)
202C--------------------------------------------------
203C PRINT
204C--------------------------------------------------
205 j=0
206 RETURN
207C
2082000 FORMAT(/, ' INITIAL TEMPERATURE ',/' -------------------',//
209 + 6x,'NODE',17x,'TEMP ' )
210 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_float_array_index(name, rval, index, is_available, lsubmodel, unitab)
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
integer, parameter ncharkey
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
integer function usr2sys(iu, itabm1, mess, id)
Definition sysfus.F:160
subroutine udouble(list, ilist, nlist, mess, ir, rlist)
Definition sysfus.F:589