OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_prop_user.F File Reference
#include "implicit_f.inc"
#include "scr15_c.inc"
#include "param_c.inc"
#include "userlib.inc"
#include "tablen_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_prop_user (iout, nuvar, pargeo, unitab, igtyp, ig, title, lsubmodel, iunit, iskn, key, prop_tag)

Function/Subroutine Documentation

◆ hm_read_prop_user()

subroutine hm_read_prop_user ( integer, intent(in) iout,
integer, dimension(2) nuvar,
pargeo,
type (unit_type_), intent(in) unitab,
integer, intent(inout) igtyp,
integer, intent(in) ig,
character(len=nchartitle) title,
type (submodel_data), dimension(nsubmod) lsubmodel,
integer, intent(in) iunit,
integer, dimension(liskn,*), intent(in) iskn,
character(len=ncharkey) key,
type(prop_tag_), dimension(0:maxprop) prop_tag )

Definition at line 38 of file hm_read_prop_user.F.

41C-----------------------------------------------
42C ROUTINE DESCRIPTION :
43C ===================
44C Read spring user property - generic routine
45C------------------------------------------------------------------
46C DUMMY ARGUMENTS DESCRIPTION:
47C ===================
48C
49C NAME DESCRIPTION
50C
51C USERL_AVAIL Flag if userlibrary was load
52C IS_AVAILABLE Bool / Result of HM_interface
53C LSUBMODEL SUBMODEL Structure.
54C------------------------------------------------------------------
55C
56C-----------------------------------------------
57C M o d u l e s
58C-----------------------------------------------
59 USE unitab_mod
60 USE message_mod
61 USE submodel_mod
62 USE elbuftag_mod
64C-----------------------------------------------
65C I m p l i c i t T y p e s
66C-----------------------------------------------
67#include "implicit_f.inc"
68C-----------------------------------------------
69C C o m m o n B l o c k s
70C-----------------------------------------------
71#include "scr15_c.inc"
72#include "param_c.inc"
73#include "userlib.inc"
74#include "tablen_c.inc"
75C-----------------------------------------------
76C D u m m y A r g u m e n t s
77C-----------------------------------------------
78 INTEGER ,INTENT(IN) :: IOUT,IG,IUNIT
79 INTEGER ,INTENT(INOUT) :: IGTYP
80 INTEGER ,INTENT(IN) :: ISKN(LISKN,*)
81 CHARACTER(LEN=ncharkey) :: KEY
82 CHARACTER(LEN=nchartitle) :: TITLE
83 INTEGER NUVAR(2)
85 . pargeo(100)
86 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
87 TYPE (SUBMODEL_DATA) ,DIMENSION(NSUBMOD) :: LSUBMODEL
88 TYPE(PROP_TAG_) , DIMENSION(0:MAXPROP) :: PROP_TAG
89C-----------------------------------------------
90C L o c a l V a r i a b l e s
91C-----------------------------------------------
92 my_real, DIMENSION(4) :: unitab_sub
93 LOGICAL :: IS_AVAILABLE
94 INTEGER J,NLINES
95 CHARACTER(LEN=NCHARLINE) :: RLINE
96 CHARACTER (LEN=4) :: CSPRI
97 CHARACTER(LEN=4096) :: SCR_FILE_NAME
98 INTEGER SCR_FILE_NAME_LEN
99 CHARACTER(LEN=NCHARLINE) :: IUSER_KEY
100!
101 CHARACTER OPTION*256
102 INTEGER SIZE
103C-----------------------------------------------
104!
105 IF(key(1:5) == 'USER1' .OR. key(1:6) == 'TYPE29')THEN
106 igtyp=29
107 ELSEIF(key(1:5) == 'USER2' .OR. key(1:6) == 'TYPE30')THEN
108 igtyp=30
109 ELSEIF(key(1:5) == 'USER3' .OR. key(1:6) == 'TYPE31')THEN
110 igtyp=31
111 ENDIF
112c--------------------------------------------------
113 is_available = .false.
114c--------------------------------------------------
115 iuser_key = key(1:len_trim(key))
116 IF (userl_avail == 0)THEN
117 ! ERROR to be printed & exit
118 option='/PROP/'//iuser_key
119 size=len_trim(option)
120 CALL ancmsg(msgid=1130,
121 . msgtype=msgerror,c1=option(1:size),anmode=aninfo)
122 CALL arret(2)
123!
124! CALL ANCMSG(MSGID=2042,
125! . ANMODE=ANINFO,
126! . MSGTYPE=MSGERROR,
127! . I1=IG,
128! . I2=IGTYP,
129! . C1=TITLE)
130 ENDIF
131!------------
132! READING
133!------------
134 WRITE(iout,1000) ig
135!
136 CALL hm_get_intv ('Number_of_datalines' ,nlines ,is_available, lsubmodel)
137!
138! IF (NLINES > 1) THEN
139!
140 WRITE(cspri,'(I4.4)')igtyp
141 scr_file_name='SI'//rootnam(1:rootlen)//'_'//cspri//'.scr'
142 scr_file_name_len=len_trim(scr_file_name)
143 OPEN(unit=30,file=trim(scr_file_name),form='FORMATTED',recl=ncharline)
144!
145 ! Read & Dump in scratch file
146! DO J=2,NLINES
147 DO j=1,nlines
148 CALL hm_get_string_index('arraydatalines', rline, j, ncharline, is_available)
149 WRITE(30,fmt='(A)')trim(rline)
150 ENDDO
151 CLOSE(unit=30)
152!
153 unitab_sub(1)=unitab%UNIT_ID(iunit)
154 unitab_sub(2)=unitab%FAC_M(iunit)
155 unitab_sub(3)=unitab%FAC_L(iunit)
156 unitab_sub(4)=unitab%FAC_T(iunit)
157!
158 CALL st_userlib_lecguser(igtyp,rootnam,rootlen,nuvar ,pargeo,unitab_sub,iskn,ig,title)
159 CALL user_output(iout,igtyp,rootnam,rootlen,1)
160!
161! ELSE
162! error TBD
163! ENDIF ! IF(NLINES > 0)THEN
164!---------
165 prop_tag(igtyp)%G_EINT = 1
166 prop_tag(igtyp)%G_FOR = 3
167 prop_tag(igtyp)%G_MOM = 5
168 prop_tag(igtyp)%G_SKEW = 6
169 prop_tag(igtyp)%G_MASS = 1
170 prop_tag(igtyp)%G_V_REPCVT = 3 ! -- VITESSES REPERE CONVECTEE (V_REPCVT)
171 prop_tag(igtyp)%G_VR_REPCVT = 3 ! -- VITESSES REPERE CONVECTEE (VR_REPCVT)
172 !
173 prop_tag(igtyp)%G_NUVAR = max(prop_tag(igtyp)%G_NUVAR,nuvar(1))
174 !
175 !---------
176 RETURN
177!---
178 1000 FORMAT(
179 & 5x,'USER PROPERTY SET'/,
180 & 5x,'PROPERTY SET NUMBER . . . . . . . . . .=',i10)
181!---
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_get_string_index(name, sval, index, size, is_available)
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle
integer, parameter ncharkey
integer, parameter ncharline
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
subroutine arret(nn)
Definition arret.F:87
subroutine user_output(iout, ilaw, rootn, rootlen, inpf)
Definition user_output.F:38