OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
lecfill.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 lecfill (ixs, fillsol, unitab, lsubmodel)

Function/Subroutine Documentation

◆ lecfill()

subroutine lecfill ( integer, dimension(nixs,*) ixs,
fillsol,
type (unit_type_), intent(in) unitab,
type(submodel_data), dimension(*) lsubmodel )

Definition at line 41 of file lecfill.F.

42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE message_mod
46 USE submodel_mod
47 USE unitab_mod
50C-----------------------------------------------
51C I m p l i c i t T y p e s
52C-----------------------------------------------
53#include "implicit_f.inc"
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57#include "com01_c.inc"
58#include "com04_c.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 INTEGER IXS(NIXS,*)
63 my_real fillsol(*)
64 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
65 TYPE(SUBMODEL_DATA) LSUBMODEL(*)
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER
70 . INI,J,N,ID_ELEM,IE,UID,SUB_ID,STAT,NB_INIBRI,
71 . IFLAGUNIT,IUNIT,NB_ELEMENTS
72 INTEGER WORKS(70000)
73 INTEGER, DIMENSION(:), ALLOCATABLE :: KSYSUSRS,INDEXS,ITRIS
74 CHARACTER MESS*40
75 CHARACTER(LEN=NCHARKEY) :: KEY
76 my_real fill
77 LOGICAL IS_AVAILABLE
78 INTEGER UEL2SYS
79 EXTERNAL uel2sys
80C=======================================================================
81 DO n=1,numels
82 fillsol(n)=one
83 END DO
84C------------------------------------
85 is_available = .false.
86!-----------------------------------------
87! pre lecture of FILL for interfaces stiffness computation
88! --- /INIBRI/FILL ---
89!-----------------------------------------
90 CALL hm_option_count('/INIBRI', nb_inibri)
91!
92 IF ( nb_inibri > 0 ) THEN
93!
94 ! Start reading /INIBRI card
95 CALL hm_option_start('/INIBRI')
96!
97 nfilsol=0
98 DO ini=1,nb_inibri
99!
100 CALL hm_option_read_key(lsubmodel,
101 . unit_id = uid,
102 . submodel_id = sub_id,
103 . keyword2 = key)
104!
105 SELECT CASE (key(1:len_trim(key)))
106 CASE ( 'FILL' )
107 nfilsol = 1
108 END SELECT ! SELECT CASE(KEY)
109!
110 ENDDO ! DO INI=1,NB_INIBRI
111C---------
112C---------
113 IF(nfilsol==0)RETURN
114C---------
115C---------
116C------------------------------------
117 ALLOCATE (itris(numels) ,stat=stat)
118 IF (stat /= 0) THEN
119 CALL ancmsg(msgid=268,anmode=aninfo,
120 . msgtype=msgerror,
121 . c1='ITRIS')
122 RETURN
123 END IF
124 ALLOCATE (indexs(2*numels) ,stat=stat)
125 IF (stat /= 0) THEN
126 CALL ancmsg(msgid=268,anmode=aninfo,
127 . msgtype=msgerror,
128 . c1='INDEXS')
129 RETURN
130 END IF
131 ALLOCATE (ksysusrs(2*numels) ,stat=stat)
132 IF (stat /= 0) THEN
133 CALL ancmsg(msgid=268,anmode=aninfo,
134 . msgtype=msgerror,
135 . c1='KSYSUSRS')
136 RETURN
137 END IF
138 itris = 0
139 indexs = 0
140 ksysusrs=0
141!
142 DO ie = 1, numels
143 itris(ie) = ixs(nixs,ie)
144 END DO
145 CALL my_orders(0,works,itris,indexs,numels,1)
146 DO j = 1, numels
147 ie=indexs(j)
148 ksysusrs(j) =ixs(nixs,ie)
149 ksysusrs(numels+j)=ie
150 END DO
151C------------------------------------
152 CALL hm_option_start('/INIBRI')
153 DO ini=1,nb_inibri
154!
155 CALL hm_option_read_key(lsubmodel,
156 . unit_id = uid,
157 . submodel_id = sub_id,
158 . keyword2 = key)
159!
160 iflagunit = 0
161 DO iunit=1,unitab%NUNITS
162 IF (unitab%UNIT_ID(iunit) == uid) THEN
163 iflagunit = 1
164 EXIT
165 ENDIF
166 ENDDO
167 IF (uid/=0.AND.iflagunit == 0) THEN
168 CALL ancmsg(msgid=659,anmode=aninfo,msgtype=msgerror,
169 . i2=uid,i1=sub_id,c1='INIBRI',
170 . c2='INIBRI',c3=' ')
171 ENDIF
172c---------------------------------------
173 SELECT CASE (key(1:len_trim(key)))
174C---------
175 CASE ( 'FILL' )
176C---------
177 nfilsol = 1
178 CALL hm_get_intv('inibri_fill_count',nb_elements,is_available,lsubmodel)
179!
180 DO j=1,nb_elements
181 ! Reading --- ID_ELEM, FILL ---
182 CALL hm_get_int_array_index('brick_ID',id_elem,j,is_available,lsubmodel)
183 CALL hm_get_float_array_index('value',fill,j,is_available,lsubmodel,unitab)
184!
185 ie=uel2sys(id_elem,ksysusrs,numels)
186 IF(ie/=0) fillsol(ie)=fill
187 ENDDO ! DO J=1,NB_ELEMENTS
188C---------
189 END SELECT ! SELECT CASE(KEY)
190!
191 ENDDO ! DO INI=1,NB_INIBRI
192!
193 DEALLOCATE(ksysusrs,indexs,itris)
194!
195 ENDIF ! IF ( NB_INIBRI > 0 ) THEN
196!
197C-----------------------------------------------
198 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_float_array_index(name, rval, index, 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_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
void my_orders(int *mode, int *iwork, int *data, int *index, int *n, int *irecl)
Definition my_orders.c:82
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 uel2sys(iu, ksysusr, numel)
Definition yctrl.F:408